@@ -115,6 +115,7 @@ module testdrive
115115 public :: test_interface, collect_interface
116116 public :: get_argument, get_variable, to_string
117117 public :: junit_output, junit_header
118+ public :: init_color_output
118119
119120
120121 ! > Single precision real numbers
@@ -336,6 +337,66 @@ end subroutine collect_interface
336337 end type junit_output
337338
338339
340+ ! > Container for terminal escape code
341+ type :: color_code
342+ ! > Style descriptor
343+ integer (i1) :: style = - 1_i1
344+ ! > Background color descriptor
345+ integer (i1) :: bg = - 1_i1
346+ ! > Foreground color descriptor
347+ integer (i1) :: fg = - 1_i1
348+ end type color_code
349+
350+ interface operator (+ )
351+ module procedure :: add_color
352+ end interface operator (+ )
353+
354+ interface operator (// )
355+ module procedure :: concat_color_left
356+ module procedure :: concat_color_right
357+ end interface operator (// )
358+
359+
360+ ! > Colorizer class for handling colorful output in the terminal
361+ type, public :: color_output
362+
363+ type (color_code) :: &
364+ reset = color_code(), &
365+ bold = color_code(), &
366+ dim = color_code(), &
367+ italic = color_code(), &
368+ underline = color_code(), &
369+ blink = color_code(), &
370+ reverse = color_code(), &
371+ hidden = color_code()
372+
373+ type (color_code) :: &
374+ black = color_code(), &
375+ red = color_code(), &
376+ green = color_code(), &
377+ yellow = color_code(), &
378+ blue = color_code(), &
379+ magenta = color_code(), &
380+ cyan = color_code(), &
381+ white = color_code()
382+
383+ type (color_code) :: &
384+ bg_black = color_code(), &
385+ bg_red = color_code(), &
386+ bg_green = color_code(), &
387+ bg_yellow = color_code(), &
388+ bg_blue = color_code(), &
389+ bg_magenta = color_code(), &
390+ bg_cyan = color_code(), &
391+ bg_white = color_code()
392+ end type color_output
393+
394+ interface color_output
395+ module procedure :: new_color_output
396+ end interface color_output
397+
398+ type (color_output), protected :: color
399+
339400 character (len=* ), parameter :: fmt = ' (1x, *(1x, a))'
340401 character (len=* ), parameter :: newline = new_line(" a" )
341402
@@ -376,8 +437,11 @@ recursive subroutine run_testsuite(collect, unit, stat, parallel, junit)
376437 ! $omp if (parallel_)
377438 do it = 1 , size (testsuite)
378439 ! $omp critical(testdrive_testsuite)
379- write (unit, ' (1x, 3(1x, a), 1x, "(", i0, "/", i0, ")")' ) &
380- & " Starting" , testsuite(it)% name, " ..." , it, size (testsuite)
440+ write (unit, ' (1x, 4(1x, a))' ) &
441+ & " Starting" , (color% blue)// testsuite(it)% name// color% reset, &
442+ & color% dim// " ..." // color% reset, &
443+ & color% bold// " (" // color% cyan// to_string(it)// color% bold // &
444+ & " /" // color% cyan// to_string(size (testsuite))// color% bold // " )" // color% reset
381445 ! $omp end critical(testdrive_testsuite)
382446 call run_unittest(testsuite(it), unit, stat, junit)
383447 end do
@@ -492,30 +556,33 @@ pure subroutine make_output(output, test, error)
492556 type (error_type), intent (in ), optional :: error
493557
494558 character (len= :), allocatable :: label
495- character (len =* ), parameter :: indent = repeat ( " " , 7 ) // repeat ( " . " , 3 ) // " "
559+ type (color_code) :: label_color
496560
497561 if (test_skipped(error)) then
498- output = indent // test% name // " [SKIPPED]" &
499- & // newline // " Message: " // error% message
500- return
501- end if
502-
503- if (present (error) .neqv. test% should_fail) then
562+ label_color = color% yellow + color% bold
563+ label = " SKIPPED"
564+ else if (present (error) .neqv. test% should_fail) then
504565 if (test% should_fail) then
505- label = " [UNEXPECTED PASS]"
566+ label_color = color% magenta + color% bold
567+ label = " UNEXPECTED PASS"
506568 else
507- label = " [FAILED]"
569+ label_color = color% red + color% bold
570+ label = " FAILED"
508571 end if
509572 else
510573 if (test% should_fail) then
511- label = " [EXPECTED FAIL]"
574+ label_color = color% cyan + color% bold
575+ label = " EXPECTED FAIL"
512576 else
513- label = " [PASSED]"
577+ label_color = color% green + color% bold
578+ label = " PASSED"
514579 end if
515580 end if
516- output = indent // test% name // label
581+ output = " " // color% dim// " ..." // color% reset // " " // &
582+ & color% blue// test% name// color% reset // &
583+ & " " // color% bold// " [" // label_color// label// color% bold// " ]" // color% reset
517584 if (present (error)) then
518- output = output // newline // " Message: " // error% message
585+ output = output // newline // " " // color % bold // " Message:" // color % reset // " " // error% message
519586 end if
520587 end subroutine make_output
521588
@@ -2229,5 +2296,146 @@ elemental function is_nan_qp(val) result(is_nan)
22292296 end function is_nan_qp
22302297#endif
22312298
2299+ ! > Initialize color output
2300+ subroutine init_color_output (use_color )
2301+ ! > Enable color output
2302+ logical , intent (in ) :: use_color
2303+
2304+ color = new_color_output(use_color)
2305+ end subroutine init_color_output
2306+
2307+ ! > Create a new colorizer object
2308+ function new_color_output (use_color ) result(new)
2309+ ! > Enable color output
2310+ logical , intent (in ) :: use_color
2311+ ! > New instance of the colorizer
2312+ type (color_output) :: new
2313+
2314+ type (color_code), parameter :: &
2315+ reset = color_code(style= 0_i1 ), &
2316+ bold = color_code(style= 1_i1 ), &
2317+ dim = color_code(style= 2_i1 ), &
2318+ italic = color_code(style= 3_i1 ), &
2319+ underline = color_code(style= 4_i1 ), &
2320+ blink = color_code(style= 5_i1 ), &
2321+ reverse = color_code(style= 7_i1 ), &
2322+ hidden = color_code(style= 8_i1 )
2323+
2324+ type (color_code), parameter :: &
2325+ black = color_code(fg= 0_i1 ), &
2326+ red = color_code(fg= 1_i1 ), &
2327+ green = color_code(fg= 2_i1 ), &
2328+ yellow = color_code(fg= 3_i1 ), &
2329+ blue = color_code(fg= 4_i1 ), &
2330+ magenta = color_code(fg= 5_i1 ), &
2331+ cyan = color_code(fg= 6_i1 ), &
2332+ white = color_code(fg= 7_i1 )
2333+
2334+ type (color_code), parameter :: &
2335+ bg_black = color_code(bg= 0_i1 ), &
2336+ bg_red = color_code(bg= 1_i1 ), &
2337+ bg_green = color_code(bg= 2_i1 ), &
2338+ bg_yellow = color_code(bg= 3_i1 ), &
2339+ bg_blue = color_code(bg= 4_i1 ), &
2340+ bg_magenta = color_code(bg= 5_i1 ), &
2341+ bg_cyan = color_code(bg= 6_i1 ), &
2342+ bg_white = color_code(bg= 7_i1 )
2343+
2344+ if (use_color) then
2345+ new% reset = reset
2346+ new% bold = bold
2347+ new% dim = dim
2348+ new% italic = italic
2349+ new% underline = underline
2350+ new% blink = blink
2351+ new% reverse = reverse
2352+ new% hidden = hidden
2353+ new% black = black
2354+ new% red = red
2355+ new% green = green
2356+ new% yellow = yellow
2357+ new% blue = blue
2358+ new% magenta = magenta
2359+ new% cyan = cyan
2360+ new% white = white
2361+ new% bg_black = bg_black
2362+ new% bg_red = bg_red
2363+ new% bg_green = bg_green
2364+ new% bg_yellow = bg_yellow
2365+ new% bg_blue = bg_blue
2366+ new% bg_magenta = bg_magenta
2367+ new% bg_cyan = bg_cyan
2368+ new% bg_white = bg_white
2369+ end if
2370+ end function new_color_output
2371+
2372+ ! > Add two escape sequences, attributes in the right value override the left value ones.
2373+ pure function add_color (lval , rval ) result(code)
2374+ ! > First escape code
2375+ type (color_code), intent (in ) :: lval
2376+ ! > Second escape code
2377+ type (color_code), intent (in ) :: rval
2378+ ! > Combined escape code
2379+ type (color_code) :: code
2380+
2381+ code = color_code( &
2382+ style= merge (rval% style, lval% style, rval% style >= 0 ), &
2383+ fg= merge (rval% fg, lval% fg, rval% fg >= 0 ), &
2384+ bg= merge (rval% bg, lval% bg, rval% bg >= 0 ))
2385+ end function add_color
2386+
2387+ ! > Concatenate an escape code with a string and turn it into an actual escape sequence
2388+ pure function concat_color_left (lval , code ) result(str)
2389+ ! > String to add the escape code to
2390+ character (len=* ), intent (in ) :: lval
2391+ ! > Escape sequence
2392+ type (color_code), intent (in ) :: code
2393+ ! > Concatenated string
2394+ character (len= :), allocatable :: str
2395+
2396+ str = lval // escape_color(code)
2397+ end function concat_color_left
2398+
2399+ ! > Concatenate an escape code with a string and turn it into an actual escape sequence
2400+ pure function concat_color_right (code , rval ) result(str)
2401+ ! > String to add the escape code to
2402+ character (len=* ), intent (in ) :: rval
2403+ ! > Escape sequence
2404+ type (color_code), intent (in ) :: code
2405+ ! > Concatenated string
2406+ character (len= :), allocatable :: str
2407+
2408+ str = escape_color(code) // rval
2409+ end function concat_color_right
2410+
2411+ ! > Transform a color code into an actual ANSI escape sequence
2412+ pure function escape_color (code ) result(str)
2413+ ! > Color code to be used
2414+ type (color_code), intent (in ) :: code
2415+ ! > ANSI escape sequence representing the color code
2416+ character (len= :), allocatable :: str
2417+ character , parameter :: chars(0 :9 ) = &
2418+ [" 0" , " 1" , " 2" , " 3" , " 4" , " 5" , " 6" , " 7" , " 8" , " 9" ]
2419+
2420+ if (anycolor(code)) then
2421+ str = achar (27 ) // " [0" ! Always reset the style
2422+ if (code% style > 0 .and. code% style < 10 ) str = str // " ;" // chars(code% style)
2423+ if (code% fg >= 0 .and. code% fg < 10 ) str = str // " ;3" // chars(code% fg)
2424+ if (code% bg >= 0 .and. code% bg < 10 ) str = str // " ;4" // chars(code% bg)
2425+ str = str // " m"
2426+ else
2427+ str = " "
2428+ end if
2429+ end function escape_color
2430+
2431+ ! > Check whether the code describes any color or is just a stub
2432+ pure function anycolor (code )
2433+ ! > Escape sequence
2434+ type (color_code), intent (in ) :: code
2435+ ! > Any color / style is active
2436+ logical :: anycolor
2437+
2438+ anycolor = code% fg >= 0 .or. code% bg >= 0 .or. code% style >= 0
2439+ end function anycolor
22322440
22332441end module testdrive
0 commit comments