How to correctly use the escape codes inside an array?

For the code shown below, in normal mode (without colors), each character variable uses only one byte. With the escape code for ANSI colors, this number of bytes increases to 10.

How to correctly use escape code for ANSI colors inside an array without such an increase? Is there an alternative to using literals to add ANSI colors?

 program color_text
  
   character(len=:), allocatable :: r, y, b, p, w
   character(len=10) :: s(-10:10,-20:20)
   integer :: i, j
  
    r =char(27)//'[31m'//'F'//char(27)//'[0m'
    y =char(27)//'[33m'//'F'//char(27)//'[0m'
    b =char(27)//'[34m'//'F'//char(27)//'[0m'
  
    do i = -10, 10
       do j = -20, 20
          if((i**2 + j**2) <= 60) then
            s(i,j) = y
          elseif((i**2 + j**2) >= 150) then
            s(i,j) = b
         else
           s(i,j) = r
         end if
      end do
    end do
   
   do i = -10, 10
      write(*,*) (s(i,j),j=-20,20)
   end do
  
end program color_text
  gfortran color_text.f90 -o color_text

result

~

2 Likes

My understanding is that the escape codes become part of the character string itself, as a kind of “encoding” for the ASCII characters.

How about making a helper routine that simply prints the character with a given colour? This would avoid having to store the 10-length “encoded” characters, instead it would generate and print them on the fly. Would this kind of approach be helpful for your case? I modified your code a bit, to experiment.

program color_text
    implicit none
    character(len=:), allocatable :: r, y, b, p, w
    !character(len=10) :: s(-10:10,-20:20)
    integer :: i, j
    
    do i = -10, 10
        do j = -20, 20
            if((i**2 + j**2) <= 60) then
                call color_print('F', 'y')
            elseif((i**2 + j**2) >= 150) then
                call color_print('F', 'b')
            else
                call color_print('F', 'r')
            end if
        end do
        print *, '' ! Line break
    end do

contains
    ! Prints the character "c" in red, yellow or blue.
    subroutine color_print(c, col)
        character, intent(in) :: c
        character, intent(in) :: col
        character(len=:), allocatable :: to_print
        
        select case (col)
        case ('r')
            to_print = char(27)//'[31m'// c //char(27)//'[0m'
        case ('y')
            to_print = char(27)//'[33m'// c //char(27)//'[0m'
        case ('b')
            to_print = char(27)//'[34m'// c //char(27)//'[0m'
        end select
        
        if (allocated(to_print)) then
            write(*,fmt='(a)',advance='no') to_print
        end if
    end subroutine  
end program color_text
1 Like

Note that you need defining the color only when it changes:

$ echo -e "\e[31mRed Text\e[0m Normal \e[34mBlue Text\e[0m"

But of course, with an array of fixed length strings it’s useless… You will use 10 bytes everywhere…

I would recommend storing 2 bytes per character: one byte for the color code, and one byte for the character itself. This way, when you print, you emit the escape sequence for the color code, then emit the character. You could also optimize this and emit the escape sequence only when the color changes.

(I believe that’s how a colored text buffer was handled in MS-DOS, but it’s been many years, since I played with colored text in MS-DOS :slight_smile: )

2 Likes