M_attr(3f) - add a splash of color to Fortran terminal output

M_attr(3f) is a module for adding basic color to output when appropriate, and is available at

        git clone https://github.com/urbanjost/M_attr.git

which can be built with fpm or GNU make(1)
or just be used as a dependency in your fpm manifest file (“fpm.toml”).

     [dependencies]
        M_attr = { git = "https://github.com/urbanjost/M_attr.git" }

It is an expansion on the HTML-like text input mode (out
of several) discussed in the experimental module M_escape(3f). It
includes allowing for arrays of text that can be displayed in a block,
formal testing, and a command line example program (“tat”) that
shows how it can easily be used with external files for purposes such
as message catalogs (tat(1) cannot be built simply with make(1), but requires fpm(1)).

Another complete mini- program (“redirect”) shows how to detect if displaying
on a terminal with ifort(1) and gfortran(1) without requiring a C
interface (See M_escape(3f) for examples of how to use C to setup
for color on MSWindows when not available).

Hopefully, a splash of color may brighten your day.

I am trying to gauge interest in whether this is suitable for proposing as part of stdlib, so feedback is particularly valued.

9 Likes

I think this is certainly the kind of thing that could be useful on a regular basis. I’ll see if I can find some time to look at it.

I would be interested if the terminal detection logic could be spun off into its own project. The primary use case would be something like “A thing happened, are we running interactively? If so, ask the user what they would like to do, if not just do this.” Having that kind of thing just work and be completely portable would be very valuable I think, and it sounds like you may have solved (at least part of) it in pursuit of this project.

1 Like

I was going to open a topic about this, when this thread was suggested on the right panel.
This is absolutely great @urbanjost . Color output is not just for fun, but just to guide the eye on a very verbose output.

To add my two cents, this is what I was doing so far, which works in a bash terminal:

write(stdout,*) achar(27)//'[31m your text '//achar(27)//'[0m'

where “31” is the code for red.

@everythingfunctional also has a point in the terminal detection question.

Edit: this should be in the stdlib, IMHO.

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
3 Likes

Thanks!

For what it’s worth, in Windows you will need something like

  block
      use iso_c_binding
      
      integer(C_INT32_T), parameter :: STD_OUTPUT_HANDLE = -11_C_INT32_T
      integer(C_INT32_T), parameter :: ENABLE_VIRTUAL_TERMINAL_PROCESSING = 4_C_INT32_T
      
      type(C_PTR) :: h_console
      
      integer(C_BOOL) :: status
      integer(C_INT32_T) :: console_mode
      
      interface
          type(C_PTR) function GetStdHandle(nStdHandle) bind(C,name = 'GetStdHandle')
          import
!DIR$ ATTRIBUTES STDCALL :: GetStdHandle
!GCC$ ATTRIBUTES STDCALL :: GetStdHandle
          integer(C_INT32_T), value, intent(in) :: nStdHandle
          end function GetStdHandle
  
          integer(C_BOOL) function GetConsoleMode(hConsoleHandle,dwMode) bind(C,name = 'GetConsoleMode')
          import
!DIR$ ATTRIBUTES STDCALL :: GetConsoleMode
!GCC$ ATTRIBUTES STDCALL :: GetConsoleMode
          type(C_PTR), value, intent(in) :: hConsoleHandle
          integer(C_INT32_T), intent(out) :: dwMode
          end function GetConsoleMode
          
          integer(C_BOOL) function SetConsoleMode(hConsoleHandle,dwMode) bind(C,name = 'SetConsoleMode')
          import
!DIR$ ATTRIBUTES STDCALL :: SetConsoleMode
!GCC$ ATTRIBUTES STDCALL :: SetConsoleMode
          type(C_PTR), value, intent(in) :: hConsoleHandle
          integer(C_INT32_T), value, intent(in) :: dwMode
          end function SetConsoleMode
      end interface
     
      h_console = GetStdHandle(STD_OUTPUT_HANDLE)
      status = GetConsoleMode(h_console,console_mode)
      if (status /= 0_C_BOOL) then
          console_mode = iOr(console_mode,ENABLE_VIRTUAL_TERMINAL_PROCESSING)
          status = SetConsoleMode(h_console,console_mode)
      end if
  end block

before using the ansii codes otherwise you’ll just get the escape codes printed. The above works in ifort - requires linking with kernel32.lib - and gfortran 32 bit builds. I haven’t tried it with anything else. (If you run the .exe in a console that already has virtual terminal processing enabled then the above isn’t required but it is required if running the .exe in a new console)

Actually, due to a bug in cmd, the above can be replaced by

  call EXECUTE_COMMAND_LINE(' ')

though it’s probably not wise to rely on the bug existing in future versions.

You might also want to check out this repo GitHub - szaghi/FACE: Fortran Ansi Colors (and Styles) Environment