From a68eb7287d7f684a5321d601b932e286df46c2eb Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Sat, 27 Nov 2021 14:08:49 +0100 Subject: [PATCH 01/10] Add terminal and color escape sequences - style, foreground and background color enumerators - true color (24-bit) types - generation of escape strings via to_string function --- doc/specs/index.md | 2 + doc/specs/stdlib_terminal_color.md | 231 +++++++++++++++++++++++ src/CMakeLists.txt | 2 + src/stdlib_terminal_colors.f90 | 182 ++++++++++++++++++ src/stdlib_terminal_colors_to_string.f90 | 73 +++++++ src/tests/CMakeLists.txt | 1 + src/tests/terminal/CMakeLists.txt | 1 + src/tests/terminal/test_colors.f90 | 107 +++++++++++ 8 files changed, 599 insertions(+) create mode 100644 doc/specs/stdlib_terminal_color.md create mode 100644 src/stdlib_terminal_colors.f90 create mode 100644 src/stdlib_terminal_colors_to_string.f90 create mode 100644 src/tests/terminal/CMakeLists.txt create mode 100644 src/tests/terminal/test_colors.f90 diff --git a/doc/specs/index.md b/doc/specs/index.md index 95f08a31f..76f285262 100644 --- a/doc/specs/index.md +++ b/doc/specs/index.md @@ -33,6 +33,8 @@ This is and index/directory of the specifications (specs) for each new module/fe - [string\_type](./stdlib_string_type.html) - Basic string support - [stringlist_type](./stdlib_stringlist_type.html) - 1-Dimensional list of strings - [strings](./stdlib_strings.html) - String handling and manipulation routines + - [stringlist_type](./stdlib_stringlist_type.html) - 1-Dimensional list of strings + - [terminal_colors](./stdlib_terminal_colors.html) - Terminal color and style escape sequences - [version](./stdlib_version.html) - Version information ## Released/Stable Features & Modules diff --git a/doc/specs/stdlib_terminal_color.md b/doc/specs/stdlib_terminal_color.md new file mode 100644 index 000000000..cdd073b28 --- /dev/null +++ b/doc/specs/stdlib_terminal_color.md @@ -0,0 +1,231 @@ +--- +title: terminal colors +... + + +# The `stdlib_terminal_colors` module + +[TOC] + +## Introduction + +Support terminal escape sequences to produce styled and colored terminal output. + + +## Derived types provided + + +### ``fg_color24`` type + +The ``fg_color24`` type represent a true color (24-bit) foreground color. +It contains the members ``red``, ``blue`` and ``green`` as default integer types. + +#### Status + +Experimental + + +### ``bg_color24`` type + +The ``bg_color24`` type represent a true color (24-bit) background color. +It contains the members ``red``, ``blue`` and ``green`` as default integer types. + +#### Status + +Experimental + + +## Constants provided + +### ``style_reset`` + +Style enumerator representing a reset escape code. + + +### ``style_bold`` + +Style enumerator representing a bold escape code. + + +### ``style_dim`` + +Style enumerator representing a dim escape code. + + + +### ``style_italic`` + +Style enumerator representing an italic escape code. + + + +### ``style_underline`` + +Style enumerator representing an underline escape code. + + +### ``style_blink`` + +Style enumerator representing a blink escape code. + + +### ``style_blink_fast`` + +Style enumerator representing a (fast) blink escape code. + + +### ``style_reverse`` + +Style enumerator representing a reverse escape code. + + +### ``style_hidden`` + +Style enumerator representing a hidden escape code. + + +### ``style_strikethrough`` + +Style enumerator representing a strike-through escape code. + + +### ``fg_color_black`` + +Foreground color enumerator representing a foreground black color escape code. + + +### ``fg_color_red`` + +Foreground color enumerator representing a foreground red color escape code. + + +### ``fg_color_green`` + +Foreground color enumerator representing a foreground green color escape code. + + +### ``fg_color_yellow`` + +Foreground color enumerator representing a foreground yellow color escape code. + + +### ``fg_color_blue`` + +Foreground color enumerator representing a foreground blue color escape code. + + +### ``fg_color_magenta`` + +Foreground color enumerator representing a foreground magenta color escape code. + + +### ``fg_color_cyan`` + +Foreground color enumerator representing a foreground cyan color escape code. + + +### ``fg_color_white`` + +Foreground color enumerator representing a foreground white color escape code. + + +### ``fg_color_default`` + +Foreground color enumerator representing a foreground default color escape code. + + +### ``bg_color_black`` + +Background color enumerator representing a background black color escape code. + + +### ``bg_color_red`` + +Background color enumerator representing a background red color escape code. + + +### ``bg_color_green`` + +Background color enumerator representing a background green color escape code. + + +### ``bg_color_yellow`` + +Background color enumerator representing a background yellow color escape code. + + +### ``bg_color_blue`` + +Background color enumerator representing a background blue color escape code. + + +### ``bg_color_magenta`` + +Background color enumerator representing a background magenta color escape code. + + +### ``bg_color_cyan`` + +Background color enumerator representing a background cyan color escape code. + + +### ``bg_color_white`` + +Background color enumerator representing a background white color escape code. + + +### ``bg_color_default`` + +Background color enumerator representing a background default color escape code. + + +## Procedures and methods provided + +### ``to_string`` + +Generic interface to turn a style, foreground or background enumerator into an actual escape code string for printout. + +#### Syntax + +`string = [[stdlib_string_colors(module):to_string(interface)]] (enum)` + +#### Class + +Pure function. + +#### Argument + +``enum``: Style, foreground or background enumerator, this argument is ``intent(in)``. + +#### Result value + +The result is a default character string. + +#### Status + +Experimental + + +### ``to_string`` + +Generic interface to turn a foreground or background true color type into an actual escape code string for printout. + +#### Syntax + +`string = [[stdlib_string_colors(module):to_string(interface)]] (color24)` + +#### Class + +Pure function. + +#### Argument + +``color24``: Foreground or background true color instance, this argument is ``intent(in)``. + +#### Result value + +The result is a default character string. + +#### Status + +Experimental diff --git a/src/CMakeLists.txt b/src/CMakeLists.txt index dce8e3054..bc611171b 100644 --- a/src/CMakeLists.txt +++ b/src/CMakeLists.txt @@ -87,6 +87,8 @@ set(SRC stdlib_system.F90 stdlib_specialfunctions.f90 stdlib_specialfunctions_legendre.f90 + stdlib_terminal_colors.f90 + stdlib_terminal_colors_to_string.f90 stdlib_quadrature_gauss.f90 stdlib_stringlist_type.f90 ${outFiles} diff --git a/src/stdlib_terminal_colors.f90 b/src/stdlib_terminal_colors.f90 new file mode 100644 index 000000000..83c9a1297 --- /dev/null +++ b/src/stdlib_terminal_colors.f90 @@ -0,0 +1,182 @@ +! SPDX-Identifier: MIT + +!> Terminal color and style escape sequences +module stdlib_terminal_colors + implicit none + private + + public :: fg_color24, bg_color24 + + public :: style_reset, style_bold, style_dim, style_italic, style_underline, & + & style_blink, style_blink_fast, style_reverse, style_hidden, style_strikethrough + public :: fg_color_black, fg_color_red, fg_color_green, fg_color_yellow, fg_color_blue, & + & fg_color_magenta, fg_color_cyan, fg_color_white, fg_color_default + public :: bg_color_black, bg_color_red, bg_color_green, bg_color_yellow, bg_color_blue, & + & bg_color_magenta, bg_color_cyan, bg_color_white, bg_color_default + + public :: to_string + + + !> True color (24-bit) for foreground color + type :: fg_color24 + !> Red color component + integer :: red + !> Green color component + integer :: green + !> Blue color component + integer :: blue + end type fg_color24 + + + !> True color (24-bit) for background color + type :: bg_color24 + !> Red color component + integer :: red + !> Green color component + integer :: green + !> Blue color component + integer :: blue + end type bg_color24 + + + !> Enumerator for the terminal style + type :: style_enum + private + !> Unique identifier for the style + integer :: id + end type style_enum + + + !> Enumerator for the terminal foreground color + type :: fg_color_enum + private + !> Unique identifier for the foreground color + integer :: id + end type fg_color_enum + + + !> Enumerator for the terminal background color + type :: bg_color_enum + private + !> Unique identifier for the background color + integer :: id + end type bg_color_enum + + + !> Identifier for reset style + type(style_enum), parameter :: style_reset = style_enum(0) + !> Identifier for bold style + type(style_enum), parameter :: style_bold = style_enum(1) + !> Identifier for dim style + type(style_enum), parameter :: style_dim = style_enum(2) + !> Identifier for italic style + type(style_enum), parameter :: style_italic = style_enum(3) + !> Identifier for underline style + type(style_enum), parameter :: style_underline = style_enum(4) + !> Identifier for blink style + type(style_enum), parameter :: style_blink = style_enum(5) + !> Identifier for (fast) blink style + type(style_enum), parameter :: style_blink_fast = style_enum(6) + !> Identifier for reverse style + type(style_enum), parameter :: style_reverse = style_enum(7) + !> Identifier for hidden style + type(style_enum), parameter :: style_hidden = style_enum(8) + !> Identifier for strikethrough style + type(style_enum), parameter :: style_strikethrough = style_enum(9) + + !> Identifier for black foreground color + type(fg_color_enum), parameter :: fg_color_black = fg_color_enum(0) + !> Identifier for red foreground color + type(fg_color_enum), parameter :: fg_color_red = fg_color_enum(1) + !> Identifier for green foreground color + type(fg_color_enum), parameter :: fg_color_green = fg_color_enum(2) + !> Identifier for yellow foreground color + type(fg_color_enum), parameter :: fg_color_yellow = fg_color_enum(3) + !> Identifier for blue foreground color + type(fg_color_enum), parameter :: fg_color_blue = fg_color_enum(4) + !> Identifier for magenta foreground color + type(fg_color_enum), parameter :: fg_color_magenta = fg_color_enum(5) + !> Identifier for cyan foreground color + type(fg_color_enum), parameter :: fg_color_cyan = fg_color_enum(6) + !> Identifier for white foreground color + type(fg_color_enum), parameter :: fg_color_white = fg_color_enum(7) + !> Identifier for the default foreground color + type(fg_color_enum), parameter :: fg_color_default = fg_color_enum(9) + + !> Offset for foreground color + integer, parameter :: fg_offset = 30 + !> Prefix for foreground true color + character(len=*), parameter :: fg_color24_prefix = "38;2;" + + !> Identifier for black background color + type(bg_color_enum), parameter :: bg_color_black = bg_color_enum(0) + !> Identifier for red background color + type(bg_color_enum), parameter :: bg_color_red = bg_color_enum(1) + !> Identifier for green background color + type(bg_color_enum), parameter :: bg_color_green = bg_color_enum(2) + !> Identifier for yellow background color + type(bg_color_enum), parameter :: bg_color_yellow = bg_color_enum(3) + !> Identifier for blue background color + type(bg_color_enum), parameter :: bg_color_blue = bg_color_enum(4) + !> Identifier for magenta background color + type(bg_color_enum), parameter :: bg_color_magenta = bg_color_enum(5) + !> Identifier for cyan background color + type(bg_color_enum), parameter :: bg_color_cyan = bg_color_enum(6) + !> Identifier for white background color + type(bg_color_enum), parameter :: bg_color_white = bg_color_enum(7) + !> Identifier for the default background color + type(bg_color_enum), parameter :: bg_color_default = bg_color_enum(9) + + !> Offset for background color + integer, parameter :: bg_offset = 40 + !> Prefix for background true color + character(len=*), parameter :: bg_color24_prefix = "48;2;" + + !> Escape sequence for terminal style and color + character(len=*), parameter :: esc = achar(27) // "[" + + + interface to_string + !> Convert the style identifier to a string + pure module function to_string_style(style) result(str) + !> Identifier of style + type(style_enum), intent(in) :: style + !> Converted string + character(len=:), allocatable :: str + end function to_string_style + + !> Convert the color identifier to a string + pure module function to_string_fg_color(fg_color) result(str) + !> Identifier of foreground color + type(fg_color_enum), intent(in) :: fg_color + !> Converted string + character(len=:), allocatable :: str + end function to_string_fg_color + + !> Convert the background color identifier to a string + pure module function to_string_bg_color(bg_color) result(str) + !> Identifier of background color + type(bg_color_enum), intent(in) :: bg_color + !> Converted string + character(len=:), allocatable :: str + end function to_string_bg_color + + !> Convert foreground true color to a string + pure module function to_string_fg_color24(fg_color) result(str) + !> 24-bit foreground color + type(fg_color24), intent(in) :: fg_color + !> Converted string + character(len=:), allocatable :: str + end function to_string_fg_color24 + + !> Convert background true color to a string + pure module function to_string_bg_color24(bg_color) result(str) + !> 24-bit background color + type(bg_color24), intent(in) :: bg_color + !> Converted string + character(len=:), allocatable :: str + end function to_string_bg_color24 + end interface to_string + + +end module stdlib_terminal_colors diff --git a/src/stdlib_terminal_colors_to_string.f90 b/src/stdlib_terminal_colors_to_string.f90 new file mode 100644 index 000000000..9cf114e92 --- /dev/null +++ b/src/stdlib_terminal_colors_to_string.f90 @@ -0,0 +1,73 @@ +! SPDX-Identifier: MIT + +!> Implementation of the conversion to enumerator and identifier types to strings +submodule (stdlib_terminal_colors) stdlib_terminal_colors_to_string + use stdlib_strings, only : to_string_ => to_string + implicit none + + +contains + + +!> Convert the style identifier to a string +pure module function to_string_style(style) result(str) + !> Identifier of style + type(style_enum), intent(in) :: style + !> Converted string + character(len=:), allocatable :: str + + str = esc // to_string_(style%id) // "m" +end function to_string_style + + +!> Convert the color identifier to a string +pure module function to_string_fg_color(fg_color) result(str) + !> Identifier of foreground color + type(fg_color_enum), intent(in) :: fg_color + !> Converted string + character(len=:), allocatable :: str + + str = esc // to_string_(fg_color%id + fg_offset) // "m" +end function to_string_fg_color + + +!> Convert the background color identifier to a string +pure module function to_string_bg_color(bg_color) result(str) + !> Identifier of background color + type(bg_color_enum), intent(in) :: bg_color + !> Converted string + character(len=:), allocatable :: str + + str = esc // to_string_(bg_color%id + bg_offset) // "m" +end function to_string_bg_color + + +!> Convert foreground true color to a string +pure module function to_string_fg_color24(fg_color) result(str) + !> 24-bit foreground color + type(fg_color24), intent(in) :: fg_color + !> Converted string + character(len=:), allocatable :: str + + str = esc // fg_color24_prefix // & + & to_string_(abs(fg_color%red)) // ";" // & + & to_string_(abs(fg_color%green)) // ";" // & + & to_string_(abs(fg_color%blue)) // "m" +end function to_string_fg_color24 + + +!> Convert background true color to a string +pure module function to_string_bg_color24(bg_color) result(str) + !> 24-bit background color + type(bg_color24), intent(in) :: bg_color + !> Converted string + character(len=:), allocatable :: str + + str = esc // bg_color24_prefix // & + & to_string_(abs(bg_color%red)) // ";" // & + & to_string_(abs(bg_color%green)) // ";" // & + & to_string_(abs(bg_color%blue)) // "m" +end function to_string_bg_color24 + + +end submodule stdlib_terminal_colors_to_string diff --git a/src/tests/CMakeLists.txt b/src/tests/CMakeLists.txt index de110ca62..ec56e42a6 100644 --- a/src/tests/CMakeLists.txt +++ b/src/tests/CMakeLists.txt @@ -32,6 +32,7 @@ add_subdirectory(system) add_subdirectory(quadrature) add_subdirectory(math) add_subdirectory(stringlist) +add_subdirectory(terminal) ADDTEST(always_skip) set_tests_properties(always_skip PROPERTIES SKIP_RETURN_CODE 77) diff --git a/src/tests/terminal/CMakeLists.txt b/src/tests/terminal/CMakeLists.txt new file mode 100644 index 000000000..11b6c654c --- /dev/null +++ b/src/tests/terminal/CMakeLists.txt @@ -0,0 +1 @@ +ADDTEST(colors) diff --git a/src/tests/terminal/test_colors.f90 b/src/tests/terminal/test_colors.f90 new file mode 100644 index 000000000..42cd16fcd --- /dev/null +++ b/src/tests/terminal/test_colors.f90 @@ -0,0 +1,107 @@ +! SPDX-Identifier: MIT + +module test_colors + use stdlib_terminal_colors, only : fg_color24, bg_color24, fg_color_red, & + & bg_color_yellow, style_bold, to_string + use testdrive, only : new_unittest, unittest_type, error_type, check + implicit none + +contains + + !> Collect all exported unit tests + subroutine collect_colors(testsuite) + !> Collection of tests + type(unittest_type), allocatable, intent(out) :: testsuite(:) + + testsuite = [ & + new_unittest("fg_color24", test_fg_color24), & + new_unittest("bg_color24", test_bg_color24), & + new_unittest("fg_color", test_fg_color), & + new_unittest("bg_color", test_bg_color), & + new_unittest("style", test_style) & + ] + end subroutine collect_colors + + subroutine test_fg_color24(error) + !> Error handling + type(error_type), allocatable, intent(out) :: error + character(len=:), allocatable :: str + + str = to_string(fg_color24(1, 0, 0)) + call check(error, ichar(str(1:1)), 27) + if (allocated(error)) return + call check(error, str(2:), "[38;2;1;0;0m") + end subroutine test_fg_color24 + + subroutine test_bg_color24(error) + !> Error handling + type(error_type), allocatable, intent(out) :: error + character(len=:), allocatable :: str + + str = to_string(bg_color24(0, 1, 0)) + call check(error, ichar(str(1:1)), 27) + if (allocated(error)) return + call check(error, str(2:), "[48;2;0;1;0m") + end subroutine test_bg_color24 + + subroutine test_fg_color(error) + !> Error handling + type(error_type), allocatable, intent(out) :: error + character(len=:), allocatable :: str + + str = to_string(fg_color_red) + call check(error, ichar(str(1:1)), 27) + if (allocated(error)) return + call check(error, str(2:), "[31m") + end subroutine test_fg_color + + subroutine test_bg_color(error) + !> Error handling + type(error_type), allocatable, intent(out) :: error + character(len=:), allocatable :: str + + str = to_string(bg_color_yellow) + call check(error, ichar(str(1:1)), 27) + if (allocated(error)) return + call check(error, str(2:), "[43m") + end subroutine test_bg_color + + subroutine test_style(error) + !> Error handling + type(error_type), allocatable, intent(out) :: error + character(len=:), allocatable :: str + + str = to_string(style_bold) + call check(error, ichar(str(1:1)), 27) + if (allocated(error)) return + call check(error, str(2:), "[1m") + end subroutine test_style + +end module test_colors + + +program tester + use, intrinsic :: iso_fortran_env, only : error_unit + use testdrive, only : run_testsuite, new_testsuite, testsuite_type + use test_colors, only : collect_colors + implicit none + integer :: stat, is + type(testsuite_type), allocatable :: testsuites(:) + character(len=*), parameter :: fmt = '("#", *(1x, a))' + + stat = 0 + + testsuites = [ & + new_testsuite("colors", collect_colors) & + ] + + do is = 1, size(testsuites) + write(error_unit, fmt) "Testing:", testsuites(is)%name + call run_testsuite(testsuites(is)%collect, error_unit, stat) + end do + + if (stat > 0) then + write(error_unit, '(i0, 1x, a)') stat, "test(s) failed!" + error stop + end if +end program From ef972d2218e3a634ea33e604d87d81614008d8c1 Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Fri, 13 May 2022 09:40:12 +0200 Subject: [PATCH 02/10] Use different strategy for providing color codes --- doc/specs/stdlib_terminal_color.md | 107 ++++++++++-- src/CMakeLists.txt | 1 + src/stdlib_terminal_colors.f90 | 200 +++++++++-------------- src/stdlib_terminal_colors_operator.f90 | 48 ++++++ src/stdlib_terminal_colors_to_string.f90 | 91 ++++------- src/tests/terminal/test_colors.f90 | 33 +--- 6 files changed, 250 insertions(+), 230 deletions(-) create mode 100644 src/stdlib_terminal_colors_operator.f90 diff --git a/doc/specs/stdlib_terminal_color.md b/doc/specs/stdlib_terminal_color.md index cdd073b28..db0e9a927 100644 --- a/doc/specs/stdlib_terminal_color.md +++ b/doc/specs/stdlib_terminal_color.md @@ -15,24 +15,33 @@ Support terminal escape sequences to produce styled and colored terminal output. ## Derived types provided -### ``fg_color24`` type +### ``ansi_color`` type -The ``fg_color24`` type represent a true color (24-bit) foreground color. -It contains the members ``red``, ``blue`` and ``green`` as default integer types. +The ``ansi_color`` type represent an ANSI escape sequence with a style, forground +color and background color attribute. By default the instances of this type are +empty and represent no escape sequence. #### Status Experimental +#### Example -### ``bg_color24`` type +```fortran +program demo_color + use stdlib_terminal_colors, only : fg_color_blue, style_bold, style_reset, ansi_color, & + & operator(//), operator(+) + implicit none + type(ansi_color) :: highlight, reset -The ``bg_color24`` type represent a true color (24-bit) background color. -It contains the members ``red``, ``blue`` and ``green`` as default integer types. + print '(a)', highlight // "Dull text message" // reset -#### Status + highlight = fg_color_blue + style_bold + reset = style_reset -Experimental + print '(a)', highlight // "Colorful text message" // reset +end program demo_color +``` ## Constants provided @@ -52,13 +61,11 @@ Style enumerator representing a bold escape code. Style enumerator representing a dim escape code. - ### ``style_italic`` Style enumerator representing an italic escape code. - ### ``style_underline`` Style enumerator representing an underline escape code. @@ -187,7 +194,7 @@ Generic interface to turn a style, foreground or background enumerator into an a #### Syntax -`string = [[stdlib_string_colors(module):to_string(interface)]] (enum)` +`string = [[stdlib_string_colors(module):to_string(interface)]] (code)` #### Class @@ -195,7 +202,8 @@ Pure function. #### Argument -``enum``: Style, foreground or background enumerator, this argument is ``intent(in)``. +``code``: Style, foreground or background code of ``ansi_color`` type, + this argument is ``intent(in)``. #### Result value @@ -205,14 +213,25 @@ The result is a default character string. Experimental +#### Example -### ``to_string`` +```fortran +program demo_string + use stdlib_terminal_colors, only : fg_color_green, style_reset, to_string + implicit none -Generic interface to turn a foreground or background true color type into an actual escape code string for printout. + print '(a)', to_string(fg_color_green) // "Colorized text message" // to_string(style_reset) +end program demo_string +``` + + +### ``operator(+)`` + +Add two escape sequences, attributes in the right value override the left value ones. #### Syntax -`string = [[stdlib_string_colors(module):to_string(interface)]] (color24)` +`code = lval + rval` #### Class @@ -220,12 +239,66 @@ Pure function. #### Argument -``color24``: Foreground or background true color instance, this argument is ``intent(in)``. +``lval``: Style, foreground or background code of ``ansi_color`` type, + this argument is ``intent(in)``. +``rval``: Style, foreground or background code of ``ansi_color`` type, + this argument is ``intent(in)``. #### Result value -The result is a default character string. +The result is a style, foreground or background code of ``ansi_color`` type. #### Status Experimental + +#### Example + +```fortran +program demo_combine + use stdlib_terminal_colors, only : fg_color_red, style_bold, ansi_color + implicit none + type(ansi_color) :: bold_red + + bold_red = fg_color_red + style_bold +end program demo_combine +``` + + +### ``operator(//)`` + +Concatenate an escape code with a string and turn it into an actual escape sequence + +#### Syntax + +`code = lval + rval` + +#### Class + +Pure function. + +#### Argument + +``lval``: Style, foreground or background code of ``ansi_color`` type or a character string, + this argument is ``intent(in)``. +``rval``: Style, foreground or background code of ``ansi_color`` type or a character string, + this argument is ``intent(in)``. + +#### Result value + +The result is a character string with the escape sequence prepended or appended. + +#### Status + +Experimental + +#### Example + +```fortran +program demo_concat + use stdlib_terminal_colors, only : fg_color_red, style_reset, operator(//) + implicit none + + print '(a)', fg_color_red // "Colorized text message" // style_reset +end program demo_concat +``` diff --git a/src/CMakeLists.txt b/src/CMakeLists.txt index bc611171b..ce4a88bf0 100644 --- a/src/CMakeLists.txt +++ b/src/CMakeLists.txt @@ -88,6 +88,7 @@ set(SRC stdlib_specialfunctions.f90 stdlib_specialfunctions_legendre.f90 stdlib_terminal_colors.f90 + stdlib_terminal_colors_operator.f90 stdlib_terminal_colors_to_string.f90 stdlib_quadrature_gauss.f90 stdlib_stringlist_type.f90 diff --git a/src/stdlib_terminal_colors.f90 b/src/stdlib_terminal_colors.f90 index 83c9a1297..a59886f38 100644 --- a/src/stdlib_terminal_colors.f90 +++ b/src/stdlib_terminal_colors.f90 @@ -2,11 +2,11 @@ !> Terminal color and style escape sequences module stdlib_terminal_colors + use stdlib_kinds, only : i1 => int8 implicit none private - public :: fg_color24, bg_color24 - + public :: ansi_color public :: style_reset, style_bold, style_dim, style_italic, style_underline, & & style_blink, style_blink_fast, style_reverse, style_hidden, style_strikethrough public :: fg_color_black, fg_color_red, fg_color_green, fg_color_yellow, fg_color_blue, & @@ -14,169 +14,125 @@ module stdlib_terminal_colors public :: bg_color_black, bg_color_red, bg_color_green, bg_color_yellow, bg_color_blue, & & bg_color_magenta, bg_color_cyan, bg_color_white, bg_color_default - public :: to_string - - - !> True color (24-bit) for foreground color - type :: fg_color24 - !> Red color component - integer :: red - !> Green color component - integer :: green - !> Blue color component - integer :: blue - end type fg_color24 - - - !> True color (24-bit) for background color - type :: bg_color24 - !> Red color component - integer :: red - !> Green color component - integer :: green - !> Blue color component - integer :: blue - end type bg_color24 + public :: to_string, operator(+), operator(//) - !> Enumerator for the terminal style - type :: style_enum - private - !> Unique identifier for the style - integer :: id - end type style_enum - - - !> Enumerator for the terminal foreground color - type :: fg_color_enum - private - !> Unique identifier for the foreground color - integer :: id - end type fg_color_enum - - !> Enumerator for the terminal background color - type :: bg_color_enum + !> Container for terminal escape code + type :: ansi_color private - !> Unique identifier for the background color - integer :: id - end type bg_color_enum + !> Style descriptor + integer(i1) :: style = -1_i1 + !> Background color descriptor + integer(i1) :: bg = -1_i1 + !> Foreground color descriptor + integer(i1) :: fg = -1_i1 + end type ansi_color !> Identifier for reset style - type(style_enum), parameter :: style_reset = style_enum(0) + type(ansi_color), parameter :: style_reset = ansi_color(style=0) !> Identifier for bold style - type(style_enum), parameter :: style_bold = style_enum(1) + type(ansi_color), parameter :: style_bold = ansi_color(style=1) !> Identifier for dim style - type(style_enum), parameter :: style_dim = style_enum(2) + type(ansi_color), parameter :: style_dim = ansi_color(style=2) !> Identifier for italic style - type(style_enum), parameter :: style_italic = style_enum(3) + type(ansi_color), parameter :: style_italic = ansi_color(style=3) !> Identifier for underline style - type(style_enum), parameter :: style_underline = style_enum(4) + type(ansi_color), parameter :: style_underline = ansi_color(style=4) !> Identifier for blink style - type(style_enum), parameter :: style_blink = style_enum(5) + type(ansi_color), parameter :: style_blink = ansi_color(style=5) !> Identifier for (fast) blink style - type(style_enum), parameter :: style_blink_fast = style_enum(6) + type(ansi_color), parameter :: style_blink_fast = ansi_color(style=6) !> Identifier for reverse style - type(style_enum), parameter :: style_reverse = style_enum(7) + type(ansi_color), parameter :: style_reverse = ansi_color(style=7) !> Identifier for hidden style - type(style_enum), parameter :: style_hidden = style_enum(8) + type(ansi_color), parameter :: style_hidden = ansi_color(style=8) !> Identifier for strikethrough style - type(style_enum), parameter :: style_strikethrough = style_enum(9) + type(ansi_color), parameter :: style_strikethrough = ansi_color(style=9) !> Identifier for black foreground color - type(fg_color_enum), parameter :: fg_color_black = fg_color_enum(0) + type(ansi_color), parameter :: fg_color_black = ansi_color(fg=0) !> Identifier for red foreground color - type(fg_color_enum), parameter :: fg_color_red = fg_color_enum(1) + type(ansi_color), parameter :: fg_color_red = ansi_color(fg=1) !> Identifier for green foreground color - type(fg_color_enum), parameter :: fg_color_green = fg_color_enum(2) + type(ansi_color), parameter :: fg_color_green = ansi_color(fg=2) !> Identifier for yellow foreground color - type(fg_color_enum), parameter :: fg_color_yellow = fg_color_enum(3) + type(ansi_color), parameter :: fg_color_yellow = ansi_color(fg=3) !> Identifier for blue foreground color - type(fg_color_enum), parameter :: fg_color_blue = fg_color_enum(4) + type(ansi_color), parameter :: fg_color_blue = ansi_color(fg=4) !> Identifier for magenta foreground color - type(fg_color_enum), parameter :: fg_color_magenta = fg_color_enum(5) + type(ansi_color), parameter :: fg_color_magenta = ansi_color(fg=5) !> Identifier for cyan foreground color - type(fg_color_enum), parameter :: fg_color_cyan = fg_color_enum(6) + type(ansi_color), parameter :: fg_color_cyan = ansi_color(fg=6) !> Identifier for white foreground color - type(fg_color_enum), parameter :: fg_color_white = fg_color_enum(7) + type(ansi_color), parameter :: fg_color_white = ansi_color(fg=7) !> Identifier for the default foreground color - type(fg_color_enum), parameter :: fg_color_default = fg_color_enum(9) - - !> Offset for foreground color - integer, parameter :: fg_offset = 30 - !> Prefix for foreground true color - character(len=*), parameter :: fg_color24_prefix = "38;2;" + type(ansi_color), parameter :: fg_color_default = ansi_color(fg=9) !> Identifier for black background color - type(bg_color_enum), parameter :: bg_color_black = bg_color_enum(0) + type(ansi_color), parameter :: bg_color_black = ansi_color(bg=0) !> Identifier for red background color - type(bg_color_enum), parameter :: bg_color_red = bg_color_enum(1) + type(ansi_color), parameter :: bg_color_red = ansi_color(bg=1) !> Identifier for green background color - type(bg_color_enum), parameter :: bg_color_green = bg_color_enum(2) + type(ansi_color), parameter :: bg_color_green = ansi_color(bg=2) !> Identifier for yellow background color - type(bg_color_enum), parameter :: bg_color_yellow = bg_color_enum(3) + type(ansi_color), parameter :: bg_color_yellow = ansi_color(bg=3) !> Identifier for blue background color - type(bg_color_enum), parameter :: bg_color_blue = bg_color_enum(4) + type(ansi_color), parameter :: bg_color_blue = ansi_color(bg=4) !> Identifier for magenta background color - type(bg_color_enum), parameter :: bg_color_magenta = bg_color_enum(5) + type(ansi_color), parameter :: bg_color_magenta = ansi_color(bg=5) !> Identifier for cyan background color - type(bg_color_enum), parameter :: bg_color_cyan = bg_color_enum(6) + type(ansi_color), parameter :: bg_color_cyan = ansi_color(bg=6) !> Identifier for white background color - type(bg_color_enum), parameter :: bg_color_white = bg_color_enum(7) + type(ansi_color), parameter :: bg_color_white = ansi_color(bg=7) !> Identifier for the default background color - type(bg_color_enum), parameter :: bg_color_default = bg_color_enum(9) - - !> Offset for background color - integer, parameter :: bg_offset = 40 - !> Prefix for background true color - character(len=*), parameter :: bg_color24_prefix = "48;2;" - - !> Escape sequence for terminal style and color - character(len=*), parameter :: esc = achar(27) // "[" + type(ansi_color), parameter :: bg_color_default = ansi_color(bg=9) interface to_string - !> Convert the style identifier to a string - pure module function to_string_style(style) result(str) - !> Identifier of style - type(style_enum), intent(in) :: style - !> Converted string - character(len=:), allocatable :: str - end function to_string_style - - !> Convert the color identifier to a string - pure module function to_string_fg_color(fg_color) result(str) - !> Identifier of foreground color - type(fg_color_enum), intent(in) :: fg_color - !> Converted string + !> Transform a color code into an actual ANSI escape sequence + pure module function to_string_ansi_color(code) result(str) + !> Color code to be used + type(ansi_color), intent(in) :: code + !> ANSI escape sequence representing the color code character(len=:), allocatable :: str - end function to_string_fg_color + end function to_string_ansi_color + end interface to_string - !> Convert the background color identifier to a string - pure module function to_string_bg_color(bg_color) result(str) - !> Identifier of background color - type(bg_color_enum), intent(in) :: bg_color - !> Converted string - character(len=:), allocatable :: str - end function to_string_bg_color - !> Convert foreground true color to a string - pure module function to_string_fg_color24(fg_color) result(str) - !> 24-bit foreground color - type(fg_color24), intent(in) :: fg_color - !> Converted string + interface operator(+) + !> Add two escape sequences, attributes in the right value override the left value ones. + pure module function add(lval, rval) result(code) + !> First escape code + type(ansi_color), intent(in) :: lval + !> Second escape code + type(ansi_color), intent(in) :: rval + !> Combined escape code + type(ansi_color) :: code + end function add + end interface operator(+) + + interface operator(//) + !> Concatenate an escape code with a string and turn it into an actual escape sequence + pure module function concat_left(lval, code) result(str) + !> String to add the escape code to + character(len=*), intent(in) :: lval + !> Escape sequence + type(ansi_color), intent(in) :: code + !> Concatenated string character(len=:), allocatable :: str - end function to_string_fg_color24 - - !> Convert background true color to a string - pure module function to_string_bg_color24(bg_color) result(str) - !> 24-bit background color - type(bg_color24), intent(in) :: bg_color - !> Converted string + end function concat_left + + !> Concatenate an escape code with a string and turn it into an actual escape sequence + pure module function concat_right(code, rval) result(str) + !> String to add the escape code to + character(len=*), intent(in) :: rval + !> Escape sequence + type(ansi_color), intent(in) :: code + !> Concatenated string character(len=:), allocatable :: str - end function to_string_bg_color24 - end interface to_string - + end function concat_right + end interface operator(//) end module stdlib_terminal_colors diff --git a/src/stdlib_terminal_colors_operator.f90 b/src/stdlib_terminal_colors_operator.f90 new file mode 100644 index 000000000..8a42aa96f --- /dev/null +++ b/src/stdlib_terminal_colors_operator.f90 @@ -0,0 +1,48 @@ +! SPDX-Identifier: MIT + +!> Implementation of the conversion to enumerator and identifier types to strings +submodule (stdlib_terminal_colors) stdlib_terminal_colors_operator + implicit none + +contains + + !> Add two escape sequences, attributes in the right value override the left value ones. + pure module function add(lval, rval) result(code) + !> First escape code + type(ansi_color), intent(in) :: lval + !> Second escape code + type(ansi_color), intent(in) :: rval + !> Combined escape code + type(ansi_color) :: code + + code = ansi_color( & + style=merge(rval%style, lval%style, rval%style >= 0), & + fg=merge(rval%fg, lval%fg, rval%fg >= 0), & + bg=merge(rval%bg, lval%bg, rval%bg >= 0)) + end function add + + !> Concatenate an escape code with a string and turn it into an actual escape sequence + pure module function concat_left(lval, code) result(str) + !> String to add the escape code to + character(len=*), intent(in) :: lval + !> Escape sequence + type(ansi_color), intent(in) :: code + !> Concatenated string + character(len=:), allocatable :: str + + str = lval // to_string(code) + end function concat_left + + !> Concatenate an escape code with a string and turn it into an actual escape sequence + pure module function concat_right(code, rval) result(str) + !> String to add the escape code to + character(len=*), intent(in) :: rval + !> Escape sequence + type(ansi_color), intent(in) :: code + !> Concatenated string + character(len=:), allocatable :: str + + str = to_string(code) // rval + end function concat_right + +end submodule stdlib_terminal_colors_operator diff --git a/src/stdlib_terminal_colors_to_string.f90 b/src/stdlib_terminal_colors_to_string.f90 index 9cf114e92..cd9e46222 100644 --- a/src/stdlib_terminal_colors_to_string.f90 +++ b/src/stdlib_terminal_colors_to_string.f90 @@ -2,72 +2,39 @@ !> Implementation of the conversion to enumerator and identifier types to strings submodule (stdlib_terminal_colors) stdlib_terminal_colors_to_string - use stdlib_strings, only : to_string_ => to_string implicit none + character, parameter :: chars(0:9) = & + ["0", "1", "2", "3", "4", "5", "6", "7", "8", "9"] contains - -!> Convert the style identifier to a string -pure module function to_string_style(style) result(str) - !> Identifier of style - type(style_enum), intent(in) :: style - !> Converted string - character(len=:), allocatable :: str - - str = esc // to_string_(style%id) // "m" -end function to_string_style - - -!> Convert the color identifier to a string -pure module function to_string_fg_color(fg_color) result(str) - !> Identifier of foreground color - type(fg_color_enum), intent(in) :: fg_color - !> Converted string - character(len=:), allocatable :: str - - str = esc // to_string_(fg_color%id + fg_offset) // "m" -end function to_string_fg_color - - -!> Convert the background color identifier to a string -pure module function to_string_bg_color(bg_color) result(str) - !> Identifier of background color - type(bg_color_enum), intent(in) :: bg_color - !> Converted string - character(len=:), allocatable :: str - - str = esc // to_string_(bg_color%id + bg_offset) // "m" -end function to_string_bg_color - - -!> Convert foreground true color to a string -pure module function to_string_fg_color24(fg_color) result(str) - !> 24-bit foreground color - type(fg_color24), intent(in) :: fg_color - !> Converted string - character(len=:), allocatable :: str - - str = esc // fg_color24_prefix // & - & to_string_(abs(fg_color%red)) // ";" // & - & to_string_(abs(fg_color%green)) // ";" // & - & to_string_(abs(fg_color%blue)) // "m" -end function to_string_fg_color24 - - -!> Convert background true color to a string -pure module function to_string_bg_color24(bg_color) result(str) - !> 24-bit background color - type(bg_color24), intent(in) :: bg_color - !> Converted string - character(len=:), allocatable :: str - - str = esc // bg_color24_prefix // & - & to_string_(abs(bg_color%red)) // ";" // & - & to_string_(abs(bg_color%green)) // ";" // & - & to_string_(abs(bg_color%blue)) // "m" -end function to_string_bg_color24 - + !> Transform a color code into an actual ANSI escape sequence + pure module function to_string_ansi_color(code) result(str) + !> Color code to be used + type(ansi_color), intent(in) :: code + !> ANSI escape sequence representing the color code + character(len=:), allocatable :: str + + if (anycolor(code)) then + str = achar(27) // "[0" ! Always reset the style + if (code%style > 0 .and. code%style < 10) str = str // ";" // chars(code%style) + if (code%fg >= 0 .and. code%fg < 10) str = str // ";3" // chars(code%fg) + if (code%bg >= 0 .and. code%bg < 10) str = str // ";4" // chars(code%bg) + str = str // "m" + else + str = "" + end if + end function to_string_ansi_color + + !> Check whether the code describes any color or is just a stub + pure function anycolor(code) + !> Escape sequence + type(ansi_color), intent(in) :: code + !> Any color / style is active + logical :: anycolor + + anycolor = code%fg >= 0 .or. code%bg >= 0 .or. code%style >= 0 + end function anycolor end submodule stdlib_terminal_colors_to_string diff --git a/src/tests/terminal/test_colors.f90 b/src/tests/terminal/test_colors.f90 index 42cd16fcd..8bf2d5645 100644 --- a/src/tests/terminal/test_colors.f90 +++ b/src/tests/terminal/test_colors.f90 @@ -1,8 +1,7 @@ ! SPDX-Identifier: MIT module test_colors - use stdlib_terminal_colors, only : fg_color24, bg_color24, fg_color_red, & - & bg_color_yellow, style_bold, to_string + use stdlib_terminal_colors, only : fg_color_red, bg_color_yellow, style_bold, to_string use testdrive, only : new_unittest, unittest_type, error_type, check implicit none @@ -14,36 +13,12 @@ subroutine collect_colors(testsuite) type(unittest_type), allocatable, intent(out) :: testsuite(:) testsuite = [ & - new_unittest("fg_color24", test_fg_color24), & - new_unittest("bg_color24", test_bg_color24), & new_unittest("fg_color", test_fg_color), & new_unittest("bg_color", test_bg_color), & new_unittest("style", test_style) & ] end subroutine collect_colors - subroutine test_fg_color24(error) - !> Error handling - type(error_type), allocatable, intent(out) :: error - character(len=:), allocatable :: str - - str = to_string(fg_color24(1, 0, 0)) - call check(error, ichar(str(1:1)), 27) - if (allocated(error)) return - call check(error, str(2:), "[38;2;1;0;0m") - end subroutine test_fg_color24 - - subroutine test_bg_color24(error) - !> Error handling - type(error_type), allocatable, intent(out) :: error - character(len=:), allocatable :: str - - str = to_string(bg_color24(0, 1, 0)) - call check(error, ichar(str(1:1)), 27) - if (allocated(error)) return - call check(error, str(2:), "[48;2;0;1;0m") - end subroutine test_bg_color24 - subroutine test_fg_color(error) !> Error handling type(error_type), allocatable, intent(out) :: error @@ -52,7 +27,7 @@ subroutine test_fg_color(error) str = to_string(fg_color_red) call check(error, ichar(str(1:1)), 27) if (allocated(error)) return - call check(error, str(2:), "[31m") + call check(error, str(2:), "[0;31m") end subroutine test_fg_color subroutine test_bg_color(error) @@ -63,7 +38,7 @@ subroutine test_bg_color(error) str = to_string(bg_color_yellow) call check(error, ichar(str(1:1)), 27) if (allocated(error)) return - call check(error, str(2:), "[43m") + call check(error, str(2:), "[0;43m") end subroutine test_bg_color subroutine test_style(error) @@ -74,7 +49,7 @@ subroutine test_style(error) str = to_string(style_bold) call check(error, ichar(str(1:1)), 27) if (allocated(error)) return - call check(error, str(2:), "[1m") + call check(error, str(2:), "[0;1m") end subroutine test_style end module test_colors From fd319ca4f6e80a14cc5f142e6b1040632fe9a3fa Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Mon, 16 May 2022 08:12:59 +0200 Subject: [PATCH 03/10] Rename to ansi_code, initialize components Co-authored-by: Ian Giestas Pauli --- doc/specs/stdlib_terminal_color.md | 24 ++++---- src/stdlib_terminal_colors.f90 | 78 ++++++++++++------------ src/stdlib_terminal_colors_operator.f90 | 17 +++--- src/stdlib_terminal_colors_to_string.f90 | 8 +-- 4 files changed, 63 insertions(+), 64 deletions(-) diff --git a/doc/specs/stdlib_terminal_color.md b/doc/specs/stdlib_terminal_color.md index db0e9a927..88ef65b47 100644 --- a/doc/specs/stdlib_terminal_color.md +++ b/doc/specs/stdlib_terminal_color.md @@ -15,9 +15,9 @@ Support terminal escape sequences to produce styled and colored terminal output. ## Derived types provided -### ``ansi_color`` type +### ``ansi_code`` type -The ``ansi_color`` type represent an ANSI escape sequence with a style, forground +The ``ansi_code`` type represent an ANSI escape sequence with a style, forground color and background color attribute. By default the instances of this type are empty and represent no escape sequence. @@ -29,10 +29,10 @@ Experimental ```fortran program demo_color - use stdlib_terminal_colors, only : fg_color_blue, style_bold, style_reset, ansi_color, & + use stdlib_terminal_colors, only : fg_color_blue, style_bold, style_reset, ansi_code, & & operator(//), operator(+) implicit none - type(ansi_color) :: highlight, reset + type(ansi_code) :: highlight, reset print '(a)', highlight // "Dull text message" // reset @@ -202,7 +202,7 @@ Pure function. #### Argument -``code``: Style, foreground or background code of ``ansi_color`` type, +``code``: Style, foreground or background code of ``ansi_code`` type, this argument is ``intent(in)``. #### Result value @@ -239,14 +239,14 @@ Pure function. #### Argument -``lval``: Style, foreground or background code of ``ansi_color`` type, +``lval``: Style, foreground or background code of ``ansi_code`` type, this argument is ``intent(in)``. -``rval``: Style, foreground or background code of ``ansi_color`` type, +``rval``: Style, foreground or background code of ``ansi_code`` type, this argument is ``intent(in)``. #### Result value -The result is a style, foreground or background code of ``ansi_color`` type. +The result is a style, foreground or background code of ``ansi_code`` type. #### Status @@ -256,9 +256,9 @@ Experimental ```fortran program demo_combine - use stdlib_terminal_colors, only : fg_color_red, style_bold, ansi_color + use stdlib_terminal_colors, only : fg_color_red, style_bold, ansi_code implicit none - type(ansi_color) :: bold_red + type(ansi_code) :: bold_red bold_red = fg_color_red + style_bold end program demo_combine @@ -279,9 +279,9 @@ Pure function. #### Argument -``lval``: Style, foreground or background code of ``ansi_color`` type or a character string, +``lval``: Style, foreground or background code of ``ansi_code`` type or a character string, this argument is ``intent(in)``. -``rval``: Style, foreground or background code of ``ansi_color`` type or a character string, +``rval``: Style, foreground or background code of ``ansi_code`` type or a character string, this argument is ``intent(in)``. #### Result value diff --git a/src/stdlib_terminal_colors.f90 b/src/stdlib_terminal_colors.f90 index a59886f38..317fc342a 100644 --- a/src/stdlib_terminal_colors.f90 +++ b/src/stdlib_terminal_colors.f90 @@ -6,7 +6,7 @@ module stdlib_terminal_colors implicit none private - public :: ansi_color + public :: ansi_code public :: style_reset, style_bold, style_dim, style_italic, style_underline, & & style_blink, style_blink_fast, style_reverse, style_hidden, style_strikethrough public :: fg_color_black, fg_color_red, fg_color_green, fg_color_yellow, fg_color_blue, & @@ -19,7 +19,7 @@ module stdlib_terminal_colors !> Container for terminal escape code - type :: ansi_color + type :: ansi_code private !> Style descriptor integer(i1) :: style = -1_i1 @@ -27,77 +27,77 @@ module stdlib_terminal_colors integer(i1) :: bg = -1_i1 !> Foreground color descriptor integer(i1) :: fg = -1_i1 - end type ansi_color + end type ansi_code !> Identifier for reset style - type(ansi_color), parameter :: style_reset = ansi_color(style=0) + type(ansi_code), parameter :: style_reset = ansi_code(style=0) !> Identifier for bold style - type(ansi_color), parameter :: style_bold = ansi_color(style=1) + type(ansi_code), parameter :: style_bold = ansi_code(style=1) !> Identifier for dim style - type(ansi_color), parameter :: style_dim = ansi_color(style=2) + type(ansi_code), parameter :: style_dim = ansi_code(style=2) !> Identifier for italic style - type(ansi_color), parameter :: style_italic = ansi_color(style=3) + type(ansi_code), parameter :: style_italic = ansi_code(style=3) !> Identifier for underline style - type(ansi_color), parameter :: style_underline = ansi_color(style=4) + type(ansi_code), parameter :: style_underline = ansi_code(style=4) !> Identifier for blink style - type(ansi_color), parameter :: style_blink = ansi_color(style=5) + type(ansi_code), parameter :: style_blink = ansi_code(style=5) !> Identifier for (fast) blink style - type(ansi_color), parameter :: style_blink_fast = ansi_color(style=6) + type(ansi_code), parameter :: style_blink_fast = ansi_code(style=6) !> Identifier for reverse style - type(ansi_color), parameter :: style_reverse = ansi_color(style=7) + type(ansi_code), parameter :: style_reverse = ansi_code(style=7) !> Identifier for hidden style - type(ansi_color), parameter :: style_hidden = ansi_color(style=8) + type(ansi_code), parameter :: style_hidden = ansi_code(style=8) !> Identifier for strikethrough style - type(ansi_color), parameter :: style_strikethrough = ansi_color(style=9) + type(ansi_code), parameter :: style_strikethrough = ansi_code(style=9) !> Identifier for black foreground color - type(ansi_color), parameter :: fg_color_black = ansi_color(fg=0) + type(ansi_code), parameter :: fg_color_black = ansi_code(fg=0) !> Identifier for red foreground color - type(ansi_color), parameter :: fg_color_red = ansi_color(fg=1) + type(ansi_code), parameter :: fg_color_red = ansi_code(fg=1) !> Identifier for green foreground color - type(ansi_color), parameter :: fg_color_green = ansi_color(fg=2) + type(ansi_code), parameter :: fg_color_green = ansi_code(fg=2) !> Identifier for yellow foreground color - type(ansi_color), parameter :: fg_color_yellow = ansi_color(fg=3) + type(ansi_code), parameter :: fg_color_yellow = ansi_code(fg=3) !> Identifier for blue foreground color - type(ansi_color), parameter :: fg_color_blue = ansi_color(fg=4) + type(ansi_code), parameter :: fg_color_blue = ansi_code(fg=4) !> Identifier for magenta foreground color - type(ansi_color), parameter :: fg_color_magenta = ansi_color(fg=5) + type(ansi_code), parameter :: fg_color_magenta = ansi_code(fg=5) !> Identifier for cyan foreground color - type(ansi_color), parameter :: fg_color_cyan = ansi_color(fg=6) + type(ansi_code), parameter :: fg_color_cyan = ansi_code(fg=6) !> Identifier for white foreground color - type(ansi_color), parameter :: fg_color_white = ansi_color(fg=7) + type(ansi_code), parameter :: fg_color_white = ansi_code(fg=7) !> Identifier for the default foreground color - type(ansi_color), parameter :: fg_color_default = ansi_color(fg=9) + type(ansi_code), parameter :: fg_color_default = ansi_code(fg=9) !> Identifier for black background color - type(ansi_color), parameter :: bg_color_black = ansi_color(bg=0) + type(ansi_code), parameter :: bg_color_black = ansi_code(bg=0) !> Identifier for red background color - type(ansi_color), parameter :: bg_color_red = ansi_color(bg=1) + type(ansi_code), parameter :: bg_color_red = ansi_code(bg=1) !> Identifier for green background color - type(ansi_color), parameter :: bg_color_green = ansi_color(bg=2) + type(ansi_code), parameter :: bg_color_green = ansi_code(bg=2) !> Identifier for yellow background color - type(ansi_color), parameter :: bg_color_yellow = ansi_color(bg=3) + type(ansi_code), parameter :: bg_color_yellow = ansi_code(bg=3) !> Identifier for blue background color - type(ansi_color), parameter :: bg_color_blue = ansi_color(bg=4) + type(ansi_code), parameter :: bg_color_blue = ansi_code(bg=4) !> Identifier for magenta background color - type(ansi_color), parameter :: bg_color_magenta = ansi_color(bg=5) + type(ansi_code), parameter :: bg_color_magenta = ansi_code(bg=5) !> Identifier for cyan background color - type(ansi_color), parameter :: bg_color_cyan = ansi_color(bg=6) + type(ansi_code), parameter :: bg_color_cyan = ansi_code(bg=6) !> Identifier for white background color - type(ansi_color), parameter :: bg_color_white = ansi_color(bg=7) + type(ansi_code), parameter :: bg_color_white = ansi_code(bg=7) !> Identifier for the default background color - type(ansi_color), parameter :: bg_color_default = ansi_color(bg=9) + type(ansi_code), parameter :: bg_color_default = ansi_code(bg=9) interface to_string !> Transform a color code into an actual ANSI escape sequence - pure module function to_string_ansi_color(code) result(str) + pure module function to_string_ansi_code(code) result(str) !> Color code to be used - type(ansi_color), intent(in) :: code + type(ansi_code), intent(in) :: code !> ANSI escape sequence representing the color code character(len=:), allocatable :: str - end function to_string_ansi_color + end function to_string_ansi_code end interface to_string @@ -105,11 +105,11 @@ end function to_string_ansi_color !> Add two escape sequences, attributes in the right value override the left value ones. pure module function add(lval, rval) result(code) !> First escape code - type(ansi_color), intent(in) :: lval + type(ansi_code), intent(in) :: lval !> Second escape code - type(ansi_color), intent(in) :: rval + type(ansi_code), intent(in) :: rval !> Combined escape code - type(ansi_color) :: code + type(ansi_code) :: code end function add end interface operator(+) @@ -119,7 +119,7 @@ pure module function concat_left(lval, code) result(str) !> String to add the escape code to character(len=*), intent(in) :: lval !> Escape sequence - type(ansi_color), intent(in) :: code + type(ansi_code), intent(in) :: code !> Concatenated string character(len=:), allocatable :: str end function concat_left @@ -129,7 +129,7 @@ pure module function concat_right(code, rval) result(str) !> String to add the escape code to character(len=*), intent(in) :: rval !> Escape sequence - type(ansi_color), intent(in) :: code + type(ansi_code), intent(in) :: code !> Concatenated string character(len=:), allocatable :: str end function concat_right diff --git a/src/stdlib_terminal_colors_operator.f90 b/src/stdlib_terminal_colors_operator.f90 index 8a42aa96f..7b3b66ddc 100644 --- a/src/stdlib_terminal_colors_operator.f90 +++ b/src/stdlib_terminal_colors_operator.f90 @@ -9,16 +9,15 @@ !> Add two escape sequences, attributes in the right value override the left value ones. pure module function add(lval, rval) result(code) !> First escape code - type(ansi_color), intent(in) :: lval + type(ansi_code), intent(in) :: lval !> Second escape code - type(ansi_color), intent(in) :: rval + type(ansi_code), intent(in) :: rval !> Combined escape code - type(ansi_color) :: code + type(ansi_code) :: code - code = ansi_color( & - style=merge(rval%style, lval%style, rval%style >= 0), & - fg=merge(rval%fg, lval%fg, rval%fg >= 0), & - bg=merge(rval%bg, lval%bg, rval%bg >= 0)) + code%style = merge(rval%style, lval%style, rval%style >= 0) + code%fg = merge(rval%fg, lval%fg, rval%fg >= 0) + code%bg = merge(rval%bg, lval%bg, rval%bg >= 0) end function add !> Concatenate an escape code with a string and turn it into an actual escape sequence @@ -26,7 +25,7 @@ pure module function concat_left(lval, code) result(str) !> String to add the escape code to character(len=*), intent(in) :: lval !> Escape sequence - type(ansi_color), intent(in) :: code + type(ansi_code), intent(in) :: code !> Concatenated string character(len=:), allocatable :: str @@ -38,7 +37,7 @@ pure module function concat_right(code, rval) result(str) !> String to add the escape code to character(len=*), intent(in) :: rval !> Escape sequence - type(ansi_color), intent(in) :: code + type(ansi_code), intent(in) :: code !> Concatenated string character(len=:), allocatable :: str diff --git a/src/stdlib_terminal_colors_to_string.f90 b/src/stdlib_terminal_colors_to_string.f90 index cd9e46222..5caf8b064 100644 --- a/src/stdlib_terminal_colors_to_string.f90 +++ b/src/stdlib_terminal_colors_to_string.f90 @@ -10,9 +10,9 @@ contains !> Transform a color code into an actual ANSI escape sequence - pure module function to_string_ansi_color(code) result(str) + pure module function to_string_ansi_code(code) result(str) !> Color code to be used - type(ansi_color), intent(in) :: code + type(ansi_code), intent(in) :: code !> ANSI escape sequence representing the color code character(len=:), allocatable :: str @@ -25,12 +25,12 @@ pure module function to_string_ansi_color(code) result(str) else str = "" end if - end function to_string_ansi_color + end function to_string_ansi_code !> Check whether the code describes any color or is just a stub pure function anycolor(code) !> Escape sequence - type(ansi_color), intent(in) :: code + type(ansi_code), intent(in) :: code !> Any color / style is active logical :: anycolor From 30e875f5e9c230d3d7988bcc37eec31150c3967c Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Thu, 19 May 2022 23:26:15 +0200 Subject: [PATCH 04/10] Fix typo Co-authored-by: Ivan Pribec --- doc/specs/stdlib_terminal_color.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/specs/stdlib_terminal_color.md b/doc/specs/stdlib_terminal_color.md index 88ef65b47..3438bdec0 100644 --- a/doc/specs/stdlib_terminal_color.md +++ b/doc/specs/stdlib_terminal_color.md @@ -17,7 +17,7 @@ Support terminal escape sequences to produce styled and colored terminal output. ### ``ansi_code`` type -The ``ansi_code`` type represent an ANSI escape sequence with a style, forground +The ``ansi_code`` type represent an ANSI escape sequence with a style, foreground color and background color attribute. By default the instances of this type are empty and represent no escape sequence. From 8ceeb3fa6d49a7dde527fe3406216b7b05846359 Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Thu, 30 Jun 2022 10:23:01 +0200 Subject: [PATCH 05/10] Apply suggestions from code review Co-authored-by: Ivan Pribec --- doc/specs/stdlib_terminal_color.md | 2 +- src/tests/terminal/test_colors.f90 | 6 +++--- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/doc/specs/stdlib_terminal_color.md b/doc/specs/stdlib_terminal_color.md index 3438bdec0..5e1c53021 100644 --- a/doc/specs/stdlib_terminal_color.md +++ b/doc/specs/stdlib_terminal_color.md @@ -271,7 +271,7 @@ Concatenate an escape code with a string and turn it into an actual escape seque #### Syntax -`code = lval + rval` +`str = lval // rval` #### Class diff --git a/src/tests/terminal/test_colors.f90 b/src/tests/terminal/test_colors.f90 index 8bf2d5645..eeb752672 100644 --- a/src/tests/terminal/test_colors.f90 +++ b/src/tests/terminal/test_colors.f90 @@ -25,7 +25,7 @@ subroutine test_fg_color(error) character(len=:), allocatable :: str str = to_string(fg_color_red) - call check(error, ichar(str(1:1)), 27) + call check(error, iachar(str(1:1)), 27) if (allocated(error)) return call check(error, str(2:), "[0;31m") end subroutine test_fg_color @@ -36,7 +36,7 @@ subroutine test_bg_color(error) character(len=:), allocatable :: str str = to_string(bg_color_yellow) - call check(error, ichar(str(1:1)), 27) + call check(error, iachar(str(1:1)), 27) if (allocated(error)) return call check(error, str(2:), "[0;43m") end subroutine test_bg_color @@ -47,7 +47,7 @@ subroutine test_style(error) character(len=:), allocatable :: str str = to_string(style_bold) - call check(error, ichar(str(1:1)), 27) + call check(error, iachar(str(1:1)), 27) if (allocated(error)) return call check(error, str(2:), "[0;1m") end subroutine test_style From 925437fef5419684daa36d67c20183c67365847b Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Thu, 30 Jun 2022 10:24:31 +0200 Subject: [PATCH 06/10] Use constant for escape character --- src/stdlib_terminal_colors_to_string.f90 | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/stdlib_terminal_colors_to_string.f90 b/src/stdlib_terminal_colors_to_string.f90 index 5caf8b064..d83b66ba6 100644 --- a/src/stdlib_terminal_colors_to_string.f90 +++ b/src/stdlib_terminal_colors_to_string.f90 @@ -4,7 +4,7 @@ submodule (stdlib_terminal_colors) stdlib_terminal_colors_to_string implicit none - character, parameter :: chars(0:9) = & + character, parameter :: esc = achar(27), chars(0:9) = & ["0", "1", "2", "3", "4", "5", "6", "7", "8", "9"] contains @@ -17,7 +17,7 @@ pure module function to_string_ansi_code(code) result(str) character(len=:), allocatable :: str if (anycolor(code)) then - str = achar(27) // "[0" ! Always reset the style + str = esc // "[0" ! Always reset the style if (code%style > 0 .and. code%style < 10) str = str // ";" // chars(code%style) if (code%fg >= 0 .and. code%fg < 10) str = str // ";3" // chars(code%fg) if (code%bg >= 0 .and. code%bg < 10) str = str // ";4" // chars(code%bg) From 069edf0e012223e0ab554380315792206283006b Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Thu, 30 Jun 2022 10:24:48 +0200 Subject: [PATCH 07/10] Remove duplicate in index Co-authored-by: Ian Giestas Pauli --- doc/specs/index.md | 1 - 1 file changed, 1 deletion(-) diff --git a/doc/specs/index.md b/doc/specs/index.md index 76f285262..87e7fa822 100644 --- a/doc/specs/index.md +++ b/doc/specs/index.md @@ -33,7 +33,6 @@ This is and index/directory of the specifications (specs) for each new module/fe - [string\_type](./stdlib_string_type.html) - Basic string support - [stringlist_type](./stdlib_stringlist_type.html) - 1-Dimensional list of strings - [strings](./stdlib_strings.html) - String handling and manipulation routines - - [stringlist_type](./stdlib_stringlist_type.html) - 1-Dimensional list of strings - [terminal_colors](./stdlib_terminal_colors.html) - Terminal color and style escape sequences - [version](./stdlib_version.html) - Version information From d4cf0d76cf66514d0a817889919996296e1dcc97 Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Thu, 30 Jun 2022 10:25:12 +0200 Subject: [PATCH 08/10] Update docstring Co-authored-by: Ivan Pribec --- src/stdlib_terminal_colors_to_string.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/stdlib_terminal_colors_to_string.f90 b/src/stdlib_terminal_colors_to_string.f90 index d83b66ba6..db598e5ba 100644 --- a/src/stdlib_terminal_colors_to_string.f90 +++ b/src/stdlib_terminal_colors_to_string.f90 @@ -27,7 +27,7 @@ pure module function to_string_ansi_code(code) result(str) end if end function to_string_ansi_code - !> Check whether the code describes any color or is just a stub + !> Check whether the code describes any color / style or is just a stub pure function anycolor(code) !> Escape sequence type(ansi_code), intent(in) :: code From 79addb3b2a75160a8977596c89d8e35c7ceae680 Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Thu, 30 Jun 2022 10:48:31 +0200 Subject: [PATCH 09/10] Rename module to stdlib_ansi --- doc/specs/index.md | 2 +- ...tdlib_terminal_color.md => stdlib_ansi.md} | 10 +++---- src/CMakeLists.txt | 6 ++-- ...ib_terminal_colors.f90 => stdlib_ansi.f90} | 25 ++++++++++++++-- ..._operator.f90 => stdlib_ansi_operator.f90} | 29 +++++++++++++++++-- ...o_string.f90 => stdlib_ansi_to_string.f90} | 4 +-- src/tests/terminal/test_colors.f90 | 2 +- 7 files changed, 62 insertions(+), 16 deletions(-) rename doc/specs/{stdlib_terminal_color.md => stdlib_ansi.md} (94%) rename src/{stdlib_terminal_colors.f90 => stdlib_ansi.f90} (85%) rename src/{stdlib_terminal_colors_operator.f90 => stdlib_ansi_operator.f90} (60%) rename src/{stdlib_terminal_colors_to_string.f90 => stdlib_ansi_to_string.f90} (92%) diff --git a/doc/specs/index.md b/doc/specs/index.md index 87e7fa822..25d99f87b 100644 --- a/doc/specs/index.md +++ b/doc/specs/index.md @@ -11,6 +11,7 @@ This is and index/directory of the specifications (specs) for each new module/fe ## Experimental Features & Modules + - [ansi](./stdlib_ansi.html) - Terminal color and style escape sequences - [array](./stdlib_array.html) - Procedures for index manipulation and array handling - [ascii](./stdlib_ascii.html) - Procedures for handling ASCII characters - [bitsets](./stdlib_bitsets.html) - Bitset data types and procedures @@ -33,7 +34,6 @@ This is and index/directory of the specifications (specs) for each new module/fe - [string\_type](./stdlib_string_type.html) - Basic string support - [stringlist_type](./stdlib_stringlist_type.html) - 1-Dimensional list of strings - [strings](./stdlib_strings.html) - String handling and manipulation routines - - [terminal_colors](./stdlib_terminal_colors.html) - Terminal color and style escape sequences - [version](./stdlib_version.html) - Version information ## Released/Stable Features & Modules diff --git a/doc/specs/stdlib_terminal_color.md b/doc/specs/stdlib_ansi.md similarity index 94% rename from doc/specs/stdlib_terminal_color.md rename to doc/specs/stdlib_ansi.md index 5e1c53021..7fa8e8d3c 100644 --- a/doc/specs/stdlib_terminal_color.md +++ b/doc/specs/stdlib_ansi.md @@ -3,7 +3,7 @@ title: terminal colors ... -# The `stdlib_terminal_colors` module +# The `stdlib_ansi` module [TOC] @@ -29,7 +29,7 @@ Experimental ```fortran program demo_color - use stdlib_terminal_colors, only : fg_color_blue, style_bold, style_reset, ansi_code, & + use stdlib_ansi, only : fg_color_blue, style_bold, style_reset, ansi_code, & & operator(//), operator(+) implicit none type(ansi_code) :: highlight, reset @@ -217,7 +217,7 @@ Experimental ```fortran program demo_string - use stdlib_terminal_colors, only : fg_color_green, style_reset, to_string + use stdlib_ansi, only : fg_color_green, style_reset, to_string implicit none print '(a)', to_string(fg_color_green) // "Colorized text message" // to_string(style_reset) @@ -256,7 +256,7 @@ Experimental ```fortran program demo_combine - use stdlib_terminal_colors, only : fg_color_red, style_bold, ansi_code + use stdlib_ansi, only : fg_color_red, style_bold, ansi_code implicit none type(ansi_code) :: bold_red @@ -296,7 +296,7 @@ Experimental ```fortran program demo_concat - use stdlib_terminal_colors, only : fg_color_red, style_reset, operator(//) + use stdlib_ansi, only : fg_color_red, style_reset, operator(//) implicit none print '(a)', fg_color_red // "Colorized text message" // style_reset diff --git a/src/CMakeLists.txt b/src/CMakeLists.txt index ce4a88bf0..ca57f4388 100644 --- a/src/CMakeLists.txt +++ b/src/CMakeLists.txt @@ -81,15 +81,15 @@ list( fypp_f90("${fyppFlags}" "${fppFiles}" outFiles) set(SRC + stdlib_ansi.f90 + stdlib_ansi_operator.f90 + stdlib_ansi_to_string.f90 stdlib_array.f90 stdlib_error.f90 stdlib_logger.f90 stdlib_system.F90 stdlib_specialfunctions.f90 stdlib_specialfunctions_legendre.f90 - stdlib_terminal_colors.f90 - stdlib_terminal_colors_operator.f90 - stdlib_terminal_colors_to_string.f90 stdlib_quadrature_gauss.f90 stdlib_stringlist_type.f90 ${outFiles} diff --git a/src/stdlib_terminal_colors.f90 b/src/stdlib_ansi.f90 similarity index 85% rename from src/stdlib_terminal_colors.f90 rename to src/stdlib_ansi.f90 index 317fc342a..8c995770d 100644 --- a/src/stdlib_terminal_colors.f90 +++ b/src/stdlib_ansi.f90 @@ -1,8 +1,9 @@ ! SPDX-Identifier: MIT !> Terminal color and style escape sequences -module stdlib_terminal_colors +module stdlib_ansi use stdlib_kinds, only : i1 => int8 + use stdlib_string_type, only : string_type implicit none private @@ -133,6 +134,26 @@ pure module function concat_right(code, rval) result(str) !> Concatenated string character(len=:), allocatable :: str end function concat_right + + !> Concatenate an escape code with a string and turn it into an actual escape sequence + pure module function concat_left_str(lval, code) result(str) + !> String to add the escape code to + type(string_type), intent(in) :: lval + !> Escape sequence + type(ansi_code), intent(in) :: code + !> Concatenated string + type(string_type) :: str + end function concat_left_str + + !> Concatenate an escape code with a string and turn it into an actual escape sequence + pure module function concat_right_str(code, rval) result(str) + !> String to add the escape code to + type(string_type), intent(in) :: rval + !> Escape sequence + type(ansi_code), intent(in) :: code + !> Concatenated string + type(string_type) :: str + end function concat_right_str end interface operator(//) -end module stdlib_terminal_colors +end module stdlib_ansi diff --git a/src/stdlib_terminal_colors_operator.f90 b/src/stdlib_ansi_operator.f90 similarity index 60% rename from src/stdlib_terminal_colors_operator.f90 rename to src/stdlib_ansi_operator.f90 index 7b3b66ddc..9e557ec51 100644 --- a/src/stdlib_terminal_colors_operator.f90 +++ b/src/stdlib_ansi_operator.f90 @@ -1,7 +1,8 @@ ! SPDX-Identifier: MIT !> Implementation of the conversion to enumerator and identifier types to strings -submodule (stdlib_terminal_colors) stdlib_terminal_colors_operator +submodule (stdlib_ansi) stdlib_ansi_operator + use stdlib_string_type, only : operator(//) implicit none contains @@ -44,4 +45,28 @@ pure module function concat_right(code, rval) result(str) str = to_string(code) // rval end function concat_right -end submodule stdlib_terminal_colors_operator + !> Concatenate an escape code with a string and turn it into an actual escape sequence + pure module function concat_left_str(lval, code) result(str) + !> String to add the escape code to + type(string_type), intent(in) :: lval + !> Escape sequence + type(ansi_code), intent(in) :: code + !> Concatenated string + type(string_type) :: str + + str = lval // to_string(code) + end function concat_left_str + + !> Concatenate an escape code with a string and turn it into an actual escape sequence + pure module function concat_right_str(code, rval) result(str) + !> String to add the escape code to + type(string_type), intent(in) :: rval + !> Escape sequence + type(ansi_code), intent(in) :: code + !> Concatenated string + type(string_type) :: str + + str = to_string(code) // rval + end function concat_right_str + +end submodule stdlib_ansi_operator diff --git a/src/stdlib_terminal_colors_to_string.f90 b/src/stdlib_ansi_to_string.f90 similarity index 92% rename from src/stdlib_terminal_colors_to_string.f90 rename to src/stdlib_ansi_to_string.f90 index db598e5ba..1f08ab9ac 100644 --- a/src/stdlib_terminal_colors_to_string.f90 +++ b/src/stdlib_ansi_to_string.f90 @@ -1,7 +1,7 @@ ! SPDX-Identifier: MIT !> Implementation of the conversion to enumerator and identifier types to strings -submodule (stdlib_terminal_colors) stdlib_terminal_colors_to_string +submodule (stdlib_ansi) stdlib_ansi_to_string implicit none character, parameter :: esc = achar(27), chars(0:9) = & @@ -37,4 +37,4 @@ pure function anycolor(code) anycolor = code%fg >= 0 .or. code%bg >= 0 .or. code%style >= 0 end function anycolor -end submodule stdlib_terminal_colors_to_string +end submodule stdlib_ansi_to_string diff --git a/src/tests/terminal/test_colors.f90 b/src/tests/terminal/test_colors.f90 index eeb752672..e0e3d8f7e 100644 --- a/src/tests/terminal/test_colors.f90 +++ b/src/tests/terminal/test_colors.f90 @@ -1,7 +1,7 @@ ! SPDX-Identifier: MIT module test_colors - use stdlib_terminal_colors, only : fg_color_red, bg_color_yellow, style_bold, to_string + use stdlib_ansi, only : fg_color_red, bg_color_yellow, style_bold, to_string use testdrive, only : new_unittest, unittest_type, error_type, check implicit none From 8ca2ac17a13ed8752e55a80dba4561c451ce8c63 Mon Sep 17 00:00:00 2001 From: milancurcic Date: Sat, 12 Nov 2022 16:27:42 -0500 Subject: [PATCH 10/10] Move color tests to the new (test/) directory --- {src/tests => test}/terminal/CMakeLists.txt | 0 {src/tests => test}/terminal/test_colors.f90 | 0 2 files changed, 0 insertions(+), 0 deletions(-) rename {src/tests => test}/terminal/CMakeLists.txt (100%) rename {src/tests => test}/terminal/test_colors.f90 (100%) diff --git a/src/tests/terminal/CMakeLists.txt b/test/terminal/CMakeLists.txt similarity index 100% rename from src/tests/terminal/CMakeLists.txt rename to test/terminal/CMakeLists.txt diff --git a/src/tests/terminal/test_colors.f90 b/test/terminal/test_colors.f90 similarity index 100% rename from src/tests/terminal/test_colors.f90 rename to test/terminal/test_colors.f90