diff --git a/doc/specs/index.md b/doc/specs/index.md index efc601d0d..1378fa8b8 100644 --- a/doc/specs/index.md +++ b/doc/specs/index.md @@ -11,6 +11,7 @@ This is an index/directory of the specifications (specs) for each new module/fea ## 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 diff --git a/doc/specs/stdlib_ansi.md b/doc/specs/stdlib_ansi.md new file mode 100644 index 000000000..7fa8e8d3c --- /dev/null +++ b/doc/specs/stdlib_ansi.md @@ -0,0 +1,304 @@ +--- +title: terminal colors +... + + +# The `stdlib_ansi` module + +[TOC] + +## Introduction + +Support terminal escape sequences to produce styled and colored terminal output. + + +## Derived types provided + + +### ``ansi_code`` type + +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. + +#### Status + +Experimental + +#### Example + +```fortran +program demo_color + use stdlib_ansi, only : fg_color_blue, style_bold, style_reset, ansi_code, & + & operator(//), operator(+) + implicit none + type(ansi_code) :: highlight, reset + + print '(a)', highlight // "Dull text message" // reset + + highlight = fg_color_blue + style_bold + reset = style_reset + + print '(a)', highlight // "Colorful text message" // reset +end program demo_color +``` + + +## 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)]] (code)` + +#### Class + +Pure function. + +#### Argument + +``code``: Style, foreground or background code of ``ansi_code`` type, + this argument is ``intent(in)``. + +#### Result value + +The result is a default character string. + +#### Status + +Experimental + +#### Example + +```fortran +program demo_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) +end program demo_string +``` + + +### ``operator(+)`` + +Add two escape sequences, attributes in the right value override the left value ones. + +#### Syntax + +`code = lval + rval` + +#### Class + +Pure function. + +#### Argument + +``lval``: Style, foreground or background code of ``ansi_code`` type, + this argument is ``intent(in)``. +``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_code`` type. + +#### Status + +Experimental + +#### Example + +```fortran +program demo_combine + use stdlib_ansi, only : fg_color_red, style_bold, ansi_code + implicit none + type(ansi_code) :: 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 + +`str = lval // rval` + +#### Class + +Pure function. + +#### Argument + +``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_code`` 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_ansi, 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 0fb95a2d3..6f1fd0a18 100644 --- a/src/CMakeLists.txt +++ b/src/CMakeLists.txt @@ -64,6 +64,9 @@ set(fppFiles 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_hashmap_wrappers.f90 diff --git a/src/stdlib_ansi.f90 b/src/stdlib_ansi.f90 new file mode 100644 index 000000000..8c995770d --- /dev/null +++ b/src/stdlib_ansi.f90 @@ -0,0 +1,159 @@ +! SPDX-Identifier: MIT + +!> Terminal color and style escape sequences +module stdlib_ansi + use stdlib_kinds, only : i1 => int8 + use stdlib_string_type, only : string_type + implicit none + private + + 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, & + & 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, operator(+), operator(//) + + + + !> Container for terminal escape code + type :: ansi_code + private + !> 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_code + + + !> Identifier for reset style + type(ansi_code), parameter :: style_reset = ansi_code(style=0) + !> Identifier for bold style + type(ansi_code), parameter :: style_bold = ansi_code(style=1) + !> Identifier for dim style + type(ansi_code), parameter :: style_dim = ansi_code(style=2) + !> Identifier for italic style + type(ansi_code), parameter :: style_italic = ansi_code(style=3) + !> Identifier for underline style + type(ansi_code), parameter :: style_underline = ansi_code(style=4) + !> Identifier for blink style + type(ansi_code), parameter :: style_blink = ansi_code(style=5) + !> Identifier for (fast) blink style + type(ansi_code), parameter :: style_blink_fast = ansi_code(style=6) + !> Identifier for reverse style + type(ansi_code), parameter :: style_reverse = ansi_code(style=7) + !> Identifier for hidden style + type(ansi_code), parameter :: style_hidden = ansi_code(style=8) + !> Identifier for strikethrough style + type(ansi_code), parameter :: style_strikethrough = ansi_code(style=9) + + !> Identifier for black foreground color + type(ansi_code), parameter :: fg_color_black = ansi_code(fg=0) + !> Identifier for red foreground color + type(ansi_code), parameter :: fg_color_red = ansi_code(fg=1) + !> Identifier for green foreground color + type(ansi_code), parameter :: fg_color_green = ansi_code(fg=2) + !> Identifier for yellow foreground color + type(ansi_code), parameter :: fg_color_yellow = ansi_code(fg=3) + !> Identifier for blue foreground color + type(ansi_code), parameter :: fg_color_blue = ansi_code(fg=4) + !> Identifier for magenta foreground color + type(ansi_code), parameter :: fg_color_magenta = ansi_code(fg=5) + !> Identifier for cyan foreground color + type(ansi_code), parameter :: fg_color_cyan = ansi_code(fg=6) + !> Identifier for white foreground color + type(ansi_code), parameter :: fg_color_white = ansi_code(fg=7) + !> Identifier for the default foreground color + type(ansi_code), parameter :: fg_color_default = ansi_code(fg=9) + + !> Identifier for black background color + type(ansi_code), parameter :: bg_color_black = ansi_code(bg=0) + !> Identifier for red background color + type(ansi_code), parameter :: bg_color_red = ansi_code(bg=1) + !> Identifier for green background color + type(ansi_code), parameter :: bg_color_green = ansi_code(bg=2) + !> Identifier for yellow background color + type(ansi_code), parameter :: bg_color_yellow = ansi_code(bg=3) + !> Identifier for blue background color + type(ansi_code), parameter :: bg_color_blue = ansi_code(bg=4) + !> Identifier for magenta background color + type(ansi_code), parameter :: bg_color_magenta = ansi_code(bg=5) + !> Identifier for cyan background color + type(ansi_code), parameter :: bg_color_cyan = ansi_code(bg=6) + !> Identifier for white background color + type(ansi_code), parameter :: bg_color_white = ansi_code(bg=7) + !> Identifier for the default background color + 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_code(code) result(str) + !> Color code to be used + type(ansi_code), intent(in) :: code + !> ANSI escape sequence representing the color code + character(len=:), allocatable :: str + end function to_string_ansi_code + end interface to_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_code), intent(in) :: lval + !> Second escape code + type(ansi_code), intent(in) :: rval + !> Combined escape code + type(ansi_code) :: 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_code), intent(in) :: code + !> Concatenated string + character(len=:), allocatable :: str + 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_code), intent(in) :: code + !> 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_ansi diff --git a/src/stdlib_ansi_operator.f90 b/src/stdlib_ansi_operator.f90 new file mode 100644 index 000000000..9e557ec51 --- /dev/null +++ b/src/stdlib_ansi_operator.f90 @@ -0,0 +1,72 @@ +! SPDX-Identifier: MIT + +!> Implementation of the conversion to enumerator and identifier types to strings +submodule (stdlib_ansi) stdlib_ansi_operator + use stdlib_string_type, only : 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_code), intent(in) :: lval + !> Second escape code + type(ansi_code), intent(in) :: rval + !> Combined escape code + type(ansi_code) :: code + + 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 + 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_code), 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_code), intent(in) :: code + !> Concatenated string + character(len=:), allocatable :: str + + str = to_string(code) // rval + 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 + + 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_ansi_to_string.f90 b/src/stdlib_ansi_to_string.f90 new file mode 100644 index 000000000..1f08ab9ac --- /dev/null +++ b/src/stdlib_ansi_to_string.f90 @@ -0,0 +1,40 @@ +! SPDX-Identifier: MIT + +!> Implementation of the conversion to enumerator and identifier types to strings +submodule (stdlib_ansi) stdlib_ansi_to_string + implicit none + + character, parameter :: esc = achar(27), chars(0:9) = & + ["0", "1", "2", "3", "4", "5", "6", "7", "8", "9"] + +contains + + !> Transform a color code into an actual ANSI escape sequence + pure module function to_string_ansi_code(code) result(str) + !> Color code to be used + type(ansi_code), intent(in) :: code + !> ANSI escape sequence representing the color code + character(len=:), allocatable :: str + + if (anycolor(code)) then + 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) + str = str // "m" + else + str = "" + end if + end function to_string_ansi_code + + !> 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 + !> 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_ansi_to_string diff --git a/test/CMakeLists.txt b/test/CMakeLists.txt index de332abb3..7acdfba1c 100644 --- a/test/CMakeLists.txt +++ b/test/CMakeLists.txt @@ -34,6 +34,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/test/terminal/CMakeLists.txt b/test/terminal/CMakeLists.txt new file mode 100644 index 000000000..11b6c654c --- /dev/null +++ b/test/terminal/CMakeLists.txt @@ -0,0 +1 @@ +ADDTEST(colors) diff --git a/test/terminal/test_colors.f90 b/test/terminal/test_colors.f90 new file mode 100644 index 000000000..e0e3d8f7e --- /dev/null +++ b/test/terminal/test_colors.f90 @@ -0,0 +1,82 @@ +! SPDX-Identifier: MIT + +module test_colors + 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 + +contains + + !> Collect all exported unit tests + subroutine collect_colors(testsuite) + !> Collection of tests + type(unittest_type), allocatable, intent(out) :: testsuite(:) + + testsuite = [ & + 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_color(error) + !> Error handling + type(error_type), allocatable, intent(out) :: error + character(len=:), allocatable :: str + + str = to_string(fg_color_red) + call check(error, iachar(str(1:1)), 27) + if (allocated(error)) return + call check(error, str(2:), "[0;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, iachar(str(1:1)), 27) + if (allocated(error)) return + call check(error, str(2:), "[0;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, iachar(str(1:1)), 27) + if (allocated(error)) return + call check(error, str(2:), "[0;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