Skip to content

Commit f27f635

Browse files
committed
Deploying to stdlib-fpm from @ f092d06 🚀
1 parent c2012f4 commit f27f635

File tree

4 files changed

+353
-0
lines changed

4 files changed

+353
-0
lines changed

src/stdlib_ansi.f90

Lines changed: 159 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,159 @@
1+
! SPDX-Identifier: MIT
2+
3+
!> Terminal color and style escape sequences
4+
module stdlib_ansi
5+
use stdlib_kinds, only : i1 => int8
6+
use stdlib_string_type, only : string_type
7+
implicit none
8+
private
9+
10+
public :: ansi_code
11+
public :: style_reset, style_bold, style_dim, style_italic, style_underline, &
12+
& style_blink, style_blink_fast, style_reverse, style_hidden, style_strikethrough
13+
public :: fg_color_black, fg_color_red, fg_color_green, fg_color_yellow, fg_color_blue, &
14+
& fg_color_magenta, fg_color_cyan, fg_color_white, fg_color_default
15+
public :: bg_color_black, bg_color_red, bg_color_green, bg_color_yellow, bg_color_blue, &
16+
& bg_color_magenta, bg_color_cyan, bg_color_white, bg_color_default
17+
18+
public :: to_string, operator(+), operator(//)
19+
20+
21+
22+
!> Container for terminal escape code
23+
type :: ansi_code
24+
private
25+
!> Style descriptor
26+
integer(i1) :: style = -1_i1
27+
!> Background color descriptor
28+
integer(i1) :: bg = -1_i1
29+
!> Foreground color descriptor
30+
integer(i1) :: fg = -1_i1
31+
end type ansi_code
32+
33+
34+
!> Identifier for reset style
35+
type(ansi_code), parameter :: style_reset = ansi_code(style=0)
36+
!> Identifier for bold style
37+
type(ansi_code), parameter :: style_bold = ansi_code(style=1)
38+
!> Identifier for dim style
39+
type(ansi_code), parameter :: style_dim = ansi_code(style=2)
40+
!> Identifier for italic style
41+
type(ansi_code), parameter :: style_italic = ansi_code(style=3)
42+
!> Identifier for underline style
43+
type(ansi_code), parameter :: style_underline = ansi_code(style=4)
44+
!> Identifier for blink style
45+
type(ansi_code), parameter :: style_blink = ansi_code(style=5)
46+
!> Identifier for (fast) blink style
47+
type(ansi_code), parameter :: style_blink_fast = ansi_code(style=6)
48+
!> Identifier for reverse style
49+
type(ansi_code), parameter :: style_reverse = ansi_code(style=7)
50+
!> Identifier for hidden style
51+
type(ansi_code), parameter :: style_hidden = ansi_code(style=8)
52+
!> Identifier for strikethrough style
53+
type(ansi_code), parameter :: style_strikethrough = ansi_code(style=9)
54+
55+
!> Identifier for black foreground color
56+
type(ansi_code), parameter :: fg_color_black = ansi_code(fg=0)
57+
!> Identifier for red foreground color
58+
type(ansi_code), parameter :: fg_color_red = ansi_code(fg=1)
59+
!> Identifier for green foreground color
60+
type(ansi_code), parameter :: fg_color_green = ansi_code(fg=2)
61+
!> Identifier for yellow foreground color
62+
type(ansi_code), parameter :: fg_color_yellow = ansi_code(fg=3)
63+
!> Identifier for blue foreground color
64+
type(ansi_code), parameter :: fg_color_blue = ansi_code(fg=4)
65+
!> Identifier for magenta foreground color
66+
type(ansi_code), parameter :: fg_color_magenta = ansi_code(fg=5)
67+
!> Identifier for cyan foreground color
68+
type(ansi_code), parameter :: fg_color_cyan = ansi_code(fg=6)
69+
!> Identifier for white foreground color
70+
type(ansi_code), parameter :: fg_color_white = ansi_code(fg=7)
71+
!> Identifier for the default foreground color
72+
type(ansi_code), parameter :: fg_color_default = ansi_code(fg=9)
73+
74+
!> Identifier for black background color
75+
type(ansi_code), parameter :: bg_color_black = ansi_code(bg=0)
76+
!> Identifier for red background color
77+
type(ansi_code), parameter :: bg_color_red = ansi_code(bg=1)
78+
!> Identifier for green background color
79+
type(ansi_code), parameter :: bg_color_green = ansi_code(bg=2)
80+
!> Identifier for yellow background color
81+
type(ansi_code), parameter :: bg_color_yellow = ansi_code(bg=3)
82+
!> Identifier for blue background color
83+
type(ansi_code), parameter :: bg_color_blue = ansi_code(bg=4)
84+
!> Identifier for magenta background color
85+
type(ansi_code), parameter :: bg_color_magenta = ansi_code(bg=5)
86+
!> Identifier for cyan background color
87+
type(ansi_code), parameter :: bg_color_cyan = ansi_code(bg=6)
88+
!> Identifier for white background color
89+
type(ansi_code), parameter :: bg_color_white = ansi_code(bg=7)
90+
!> Identifier for the default background color
91+
type(ansi_code), parameter :: bg_color_default = ansi_code(bg=9)
92+
93+
94+
interface to_string
95+
!> Transform a color code into an actual ANSI escape sequence
96+
pure module function to_string_ansi_code(code) result(str)
97+
!> Color code to be used
98+
type(ansi_code), intent(in) :: code
99+
!> ANSI escape sequence representing the color code
100+
character(len=:), allocatable :: str
101+
end function to_string_ansi_code
102+
end interface to_string
103+
104+
105+
interface operator(+)
106+
!> Add two escape sequences, attributes in the right value override the left value ones.
107+
pure module function add(lval, rval) result(code)
108+
!> First escape code
109+
type(ansi_code), intent(in) :: lval
110+
!> Second escape code
111+
type(ansi_code), intent(in) :: rval
112+
!> Combined escape code
113+
type(ansi_code) :: code
114+
end function add
115+
end interface operator(+)
116+
117+
interface operator(//)
118+
!> Concatenate an escape code with a string and turn it into an actual escape sequence
119+
pure module function concat_left(lval, code) result(str)
120+
!> String to add the escape code to
121+
character(len=*), intent(in) :: lval
122+
!> Escape sequence
123+
type(ansi_code), intent(in) :: code
124+
!> Concatenated string
125+
character(len=:), allocatable :: str
126+
end function concat_left
127+
128+
!> Concatenate an escape code with a string and turn it into an actual escape sequence
129+
pure module function concat_right(code, rval) result(str)
130+
!> String to add the escape code to
131+
character(len=*), intent(in) :: rval
132+
!> Escape sequence
133+
type(ansi_code), intent(in) :: code
134+
!> Concatenated string
135+
character(len=:), allocatable :: str
136+
end function concat_right
137+
138+
!> Concatenate an escape code with a string and turn it into an actual escape sequence
139+
pure module function concat_left_str(lval, code) result(str)
140+
!> String to add the escape code to
141+
type(string_type), intent(in) :: lval
142+
!> Escape sequence
143+
type(ansi_code), intent(in) :: code
144+
!> Concatenated string
145+
type(string_type) :: str
146+
end function concat_left_str
147+
148+
!> Concatenate an escape code with a string and turn it into an actual escape sequence
149+
pure module function concat_right_str(code, rval) result(str)
150+
!> String to add the escape code to
151+
type(string_type), intent(in) :: rval
152+
!> Escape sequence
153+
type(ansi_code), intent(in) :: code
154+
!> Concatenated string
155+
type(string_type) :: str
156+
end function concat_right_str
157+
end interface operator(//)
158+
159+
end module stdlib_ansi

src/stdlib_ansi_operator.f90

Lines changed: 72 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,72 @@
1+
! SPDX-Identifier: MIT
2+
3+
!> Implementation of the conversion to enumerator and identifier types to strings
4+
submodule (stdlib_ansi) stdlib_ansi_operator
5+
use stdlib_string_type, only : operator(//)
6+
implicit none
7+
8+
contains
9+
10+
!> Add two escape sequences, attributes in the right value override the left value ones.
11+
pure module function add(lval, rval) result(code)
12+
!> First escape code
13+
type(ansi_code), intent(in) :: lval
14+
!> Second escape code
15+
type(ansi_code), intent(in) :: rval
16+
!> Combined escape code
17+
type(ansi_code) :: code
18+
19+
code%style = merge(rval%style, lval%style, rval%style >= 0)
20+
code%fg = merge(rval%fg, lval%fg, rval%fg >= 0)
21+
code%bg = merge(rval%bg, lval%bg, rval%bg >= 0)
22+
end function add
23+
24+
!> Concatenate an escape code with a string and turn it into an actual escape sequence
25+
pure module function concat_left(lval, code) result(str)
26+
!> String to add the escape code to
27+
character(len=*), intent(in) :: lval
28+
!> Escape sequence
29+
type(ansi_code), intent(in) :: code
30+
!> Concatenated string
31+
character(len=:), allocatable :: str
32+
33+
str = lval // to_string(code)
34+
end function concat_left
35+
36+
!> Concatenate an escape code with a string and turn it into an actual escape sequence
37+
pure module function concat_right(code, rval) result(str)
38+
!> String to add the escape code to
39+
character(len=*), intent(in) :: rval
40+
!> Escape sequence
41+
type(ansi_code), intent(in) :: code
42+
!> Concatenated string
43+
character(len=:), allocatable :: str
44+
45+
str = to_string(code) // rval
46+
end function concat_right
47+
48+
!> Concatenate an escape code with a string and turn it into an actual escape sequence
49+
pure module function concat_left_str(lval, code) result(str)
50+
!> String to add the escape code to
51+
type(string_type), intent(in) :: lval
52+
!> Escape sequence
53+
type(ansi_code), intent(in) :: code
54+
!> Concatenated string
55+
type(string_type) :: str
56+
57+
str = lval // to_string(code)
58+
end function concat_left_str
59+
60+
!> Concatenate an escape code with a string and turn it into an actual escape sequence
61+
pure module function concat_right_str(code, rval) result(str)
62+
!> String to add the escape code to
63+
type(string_type), intent(in) :: rval
64+
!> Escape sequence
65+
type(ansi_code), intent(in) :: code
66+
!> Concatenated string
67+
type(string_type) :: str
68+
69+
str = to_string(code) // rval
70+
end function concat_right_str
71+
72+
end submodule stdlib_ansi_operator

src/stdlib_ansi_to_string.f90

Lines changed: 40 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,40 @@
1+
! SPDX-Identifier: MIT
2+
3+
!> Implementation of the conversion to enumerator and identifier types to strings
4+
submodule (stdlib_ansi) stdlib_ansi_to_string
5+
implicit none
6+
7+
character, parameter :: esc = achar(27), chars(0:9) = &
8+
["0", "1", "2", "3", "4", "5", "6", "7", "8", "9"]
9+
10+
contains
11+
12+
!> Transform a color code into an actual ANSI escape sequence
13+
pure module function to_string_ansi_code(code) result(str)
14+
!> Color code to be used
15+
type(ansi_code), intent(in) :: code
16+
!> ANSI escape sequence representing the color code
17+
character(len=:), allocatable :: str
18+
19+
if (anycolor(code)) then
20+
str = esc // "[0" ! Always reset the style
21+
if (code%style > 0 .and. code%style < 10) str = str // ";" // chars(code%style)
22+
if (code%fg >= 0 .and. code%fg < 10) str = str // ";3" // chars(code%fg)
23+
if (code%bg >= 0 .and. code%bg < 10) str = str // ";4" // chars(code%bg)
24+
str = str // "m"
25+
else
26+
str = ""
27+
end if
28+
end function to_string_ansi_code
29+
30+
!> Check whether the code describes any color / style or is just a stub
31+
pure function anycolor(code)
32+
!> Escape sequence
33+
type(ansi_code), intent(in) :: code
34+
!> Any color / style is active
35+
logical :: anycolor
36+
37+
anycolor = code%fg >= 0 .or. code%bg >= 0 .or. code%style >= 0
38+
end function anycolor
39+
40+
end submodule stdlib_ansi_to_string

test/test_colors.f90

Lines changed: 82 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,82 @@
1+
! SPDX-Identifier: MIT
2+
3+
module test_colors
4+
use stdlib_ansi, only : fg_color_red, bg_color_yellow, style_bold, to_string
5+
use testdrive, only : new_unittest, unittest_type, error_type, check
6+
implicit none
7+
8+
contains
9+
10+
!> Collect all exported unit tests
11+
subroutine collect_colors(testsuite)
12+
!> Collection of tests
13+
type(unittest_type), allocatable, intent(out) :: testsuite(:)
14+
15+
testsuite = [ &
16+
new_unittest("fg_color", test_fg_color), &
17+
new_unittest("bg_color", test_bg_color), &
18+
new_unittest("style", test_style) &
19+
]
20+
end subroutine collect_colors
21+
22+
subroutine test_fg_color(error)
23+
!> Error handling
24+
type(error_type), allocatable, intent(out) :: error
25+
character(len=:), allocatable :: str
26+
27+
str = to_string(fg_color_red)
28+
call check(error, iachar(str(1:1)), 27)
29+
if (allocated(error)) return
30+
call check(error, str(2:), "[0;31m")
31+
end subroutine test_fg_color
32+
33+
subroutine test_bg_color(error)
34+
!> Error handling
35+
type(error_type), allocatable, intent(out) :: error
36+
character(len=:), allocatable :: str
37+
38+
str = to_string(bg_color_yellow)
39+
call check(error, iachar(str(1:1)), 27)
40+
if (allocated(error)) return
41+
call check(error, str(2:), "[0;43m")
42+
end subroutine test_bg_color
43+
44+
subroutine test_style(error)
45+
!> Error handling
46+
type(error_type), allocatable, intent(out) :: error
47+
character(len=:), allocatable :: str
48+
49+
str = to_string(style_bold)
50+
call check(error, iachar(str(1:1)), 27)
51+
if (allocated(error)) return
52+
call check(error, str(2:), "[0;1m")
53+
end subroutine test_style
54+
55+
end module test_colors
56+
57+
58+
program tester
59+
use, intrinsic :: iso_fortran_env, only : error_unit
60+
use testdrive, only : run_testsuite, new_testsuite, testsuite_type
61+
use test_colors, only : collect_colors
62+
implicit none
63+
integer :: stat, is
64+
type(testsuite_type), allocatable :: testsuites(:)
65+
character(len=*), parameter :: fmt = '("#", *(1x, a))'
66+
67+
stat = 0
68+
69+
testsuites = [ &
70+
new_testsuite("colors", collect_colors) &
71+
]
72+
73+
do is = 1, size(testsuites)
74+
write(error_unit, fmt) "Testing:", testsuites(is)%name
75+
call run_testsuite(testsuites(is)%collect, error_unit, stat)
76+
end do
77+
78+
if (stat > 0) then
79+
write(error_unit, '(i0, 1x, a)') stat, "test(s) failed!"
80+
error stop
81+
end if
82+
end program

0 commit comments

Comments
 (0)